OSDN Git Service

2005-09-01 Thomas Quinot <quinot@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_ch13.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             S E M _ C H 1 3                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2005, 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 2,  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 COPYING.  If not, write --
19 -- to  the  Free Software Foundation,  51  Franklin  Street,  Fifth  Floor, --
20 -- Boston, MA 02110-1301, USA.                                              --
21 --                                                                          --
22 -- GNAT was originally developed  by the GNAT team at  New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
24 --                                                                          --
25 ------------------------------------------------------------------------------
26
27 with Atree;    use Atree;
28 with Checks;   use Checks;
29 with Einfo;    use Einfo;
30 with Errout;   use Errout;
31 with Exp_Tss;  use Exp_Tss;
32 with Exp_Util; use Exp_Util;
33 with Lib;      use Lib;
34 with Nlists;   use Nlists;
35 with Nmake;    use Nmake;
36 with Opt;      use Opt;
37 with Restrict; use Restrict;
38 with Rident;   use Rident;
39 with Rtsfind;  use Rtsfind;
40 with Sem;      use Sem;
41 with Sem_Ch8;  use Sem_Ch8;
42 with Sem_Eval; use Sem_Eval;
43 with Sem_Res;  use Sem_Res;
44 with Sem_Type; use Sem_Type;
45 with Sem_Util; use Sem_Util;
46 with Snames;   use Snames;
47 with Stand;    use Stand;
48 with Sinfo;    use Sinfo;
49 with Table;
50 with Targparm; use Targparm;
51 with Ttypes;   use Ttypes;
52 with Tbuild;   use Tbuild;
53 with Urealp;   use Urealp;
54
55 with GNAT.Heap_Sort_A; use GNAT.Heap_Sort_A;
56
57 package body Sem_Ch13 is
58
59    SSU : constant Pos := System_Storage_Unit;
60    --  Convenient short hand for commonly used constant
61
62    -----------------------
63    -- Local Subprograms --
64    -----------------------
65
66    procedure Alignment_Check_For_Esize_Change (Typ : Entity_Id);
67    --  This routine is called after setting the Esize of type entity Typ.
68    --  The purpose is to deal with the situation where an aligment has been
69    --  inherited from a derived type that is no longer appropriate for the
70    --  new Esize value. In this case, we reset the Alignment to unknown.
71
72    procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id);
73    --  Given two entities for record components or discriminants, checks
74    --  if they hav overlapping component clauses and issues errors if so.
75
76    function Get_Alignment_Value (Expr : Node_Id) return Uint;
77    --  Given the expression for an alignment value, returns the corresponding
78    --  Uint value. If the value is inappropriate, then error messages are
79    --  posted as required, and a value of No_Uint is returned.
80
81    function Is_Operational_Item (N : Node_Id) return Boolean;
82    --  A specification for a stream attribute is allowed before the full
83    --  type is declared, as explained in AI-00137 and the corrigendum.
84    --  Attributes that do not specify a representation characteristic are
85    --  operational attributes.
86
87    function Address_Aliased_Entity (N : Node_Id) return Entity_Id;
88    --  If expression N is of the form E'Address, return E
89
90    procedure Mark_Aliased_Address_As_Volatile (N : Node_Id);
91    --  This is used for processing of an address representation clause. If
92    --  the expression N is of the form of K'Address, then the entity that
93    --  is associated with K is marked as volatile.
94
95    procedure New_Stream_Function
96      (N    : Node_Id;
97       Ent  : Entity_Id;
98       Subp : Entity_Id;
99       Nam  : TSS_Name_Type);
100    --  Create a function renaming of a given stream attribute to the
101    --  designated subprogram and then in the tagged case, provide this as
102    --  a primitive operation, or in the non-tagged case make an appropriate
103    --  TSS entry. Used for Input. This is more properly an expansion activity
104    --  than just semantics, but the presence of user-defined stream functions
105    --  for limited types is a legality check, which is why this takes place
106    --  here rather than in exp_ch13, where it was previously. Nam indicates
107    --  the name of the TSS function to be generated.
108    --
109    --  To avoid elaboration anomalies with freeze nodes, for untagged types
110    --  we generate both a subprogram declaration and a subprogram renaming
111    --  declaration, so that the attribute specification is handled as a
112    --  renaming_as_body. For tagged types, the specification is one of the
113    --  primitive specs.
114
115    procedure New_Stream_Procedure
116      (N     : Node_Id;
117       Ent   : Entity_Id;
118       Subp  : Entity_Id;
119       Nam   : TSS_Name_Type;
120       Out_P : Boolean := False);
121    --  Create a procedure renaming of a given stream attribute to the
122    --  designated subprogram and then in the tagged case, provide this as
123    --  a primitive operation, or in the non-tagged case make an appropriate
124    --  TSS entry. Used for Read, Output, Write. Nam indicates the name of
125    --  the TSS procedure to be generated.
126
127    ----------------------------------------------
128    -- Table for Validate_Unchecked_Conversions --
129    ----------------------------------------------
130
131    --  The following table collects unchecked conversions for validation.
132    --  Entries are made by Validate_Unchecked_Conversion and then the
133    --  call to Validate_Unchecked_Conversions does the actual error
134    --  checking and posting of warnings. The reason for this delayed
135    --  processing is to take advantage of back-annotations of size and
136    --  alignment values peformed by the back end.
137
138    type UC_Entry is record
139       Enode  : Node_Id;   -- node used for posting warnings
140       Source : Entity_Id; -- source type for unchecked conversion
141       Target : Entity_Id; -- target type for unchecked conversion
142    end record;
143
144    package Unchecked_Conversions is new Table.Table (
145      Table_Component_Type => UC_Entry,
146      Table_Index_Type     => Int,
147      Table_Low_Bound      => 1,
148      Table_Initial        => 50,
149      Table_Increment      => 200,
150      Table_Name           => "Unchecked_Conversions");
151
152    ----------------------------
153    -- Address_Aliased_Entity --
154    ----------------------------
155
156    function Address_Aliased_Entity (N : Node_Id) return Entity_Id is
157    begin
158       if Nkind (N) = N_Attribute_Reference
159         and then Attribute_Name (N) = Name_Address
160       then
161          declare
162             Nam : Node_Id := Prefix (N);
163          begin
164             while False
165               or else Nkind (Nam) = N_Selected_Component
166               or else Nkind (Nam) = N_Indexed_Component
167             loop
168                Nam := Prefix (Nam);
169             end loop;
170
171             if Is_Entity_Name (Nam) then
172                return Entity (Nam);
173             end if;
174          end;
175       end if;
176
177       return Empty;
178    end Address_Aliased_Entity;
179
180    --------------------------------------
181    -- Alignment_Check_For_Esize_Change --
182    --------------------------------------
183
184    procedure Alignment_Check_For_Esize_Change (Typ : Entity_Id) is
185    begin
186       --  If the alignment is known, and not set by a rep clause, and is
187       --  inconsistent with the size being set, then reset it to unknown,
188       --  we assume in this case that the size overrides the inherited
189       --  alignment, and that the alignment must be recomputed.
190
191       if Known_Alignment (Typ)
192         and then not Has_Alignment_Clause (Typ)
193         and then Esize (Typ) mod (Alignment (Typ) * SSU) /= 0
194       then
195          Init_Alignment (Typ);
196       end if;
197    end Alignment_Check_For_Esize_Change;
198
199    -----------------------
200    -- Analyze_At_Clause --
201    -----------------------
202
203    --  An at clause is replaced by the corresponding Address attribute
204    --  definition clause that is the preferred approach in Ada 95.
205
206    procedure Analyze_At_Clause (N : Node_Id) is
207    begin
208       Check_Restriction (No_Obsolescent_Features, N);
209
210       if Warn_On_Obsolescent_Feature then
211          Error_Msg_N
212            ("at clause is an obsolescent feature ('R'M 'J.7(2))?", N);
213          Error_Msg_N
214            ("\use address attribute definition clause instead?", N);
215       end if;
216
217       Rewrite (N,
218         Make_Attribute_Definition_Clause (Sloc (N),
219           Name  => Identifier (N),
220           Chars => Name_Address,
221           Expression => Expression (N)));
222       Analyze_Attribute_Definition_Clause (N);
223    end Analyze_At_Clause;
224
225    -----------------------------------------
226    -- Analyze_Attribute_Definition_Clause --
227    -----------------------------------------
228
229    procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
230       Loc   : constant Source_Ptr   := Sloc (N);
231       Nam   : constant Node_Id      := Name (N);
232       Attr  : constant Name_Id      := Chars (N);
233       Expr  : constant Node_Id      := Expression (N);
234       Id    : constant Attribute_Id := Get_Attribute_Id (Attr);
235       Ent   : Entity_Id;
236       U_Ent : Entity_Id;
237
238       FOnly : Boolean := False;
239       --  Reset to True for subtype specific attribute (Alignment, Size)
240       --  and for stream attributes, i.e. those cases where in the call
241       --  to Rep_Item_Too_Late, FOnly is set True so that only the freezing
242       --  rules are checked. Note that the case of stream attributes is not
243       --  clear from the RM, but see AI95-00137. Also, the RM seems to
244       --  disallow Storage_Size for derived task types, but that is also
245       --  clearly unintentional.
246
247       procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
248       --  Common processing for 'Read, 'Write, 'Input and 'Output attribute
249       --  definition clauses.
250
251       procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
252          Subp : Entity_Id := Empty;
253          I    : Interp_Index;
254          It   : Interp;
255          Pnam : Entity_Id;
256
257          Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
258
259          function Has_Good_Profile (Subp : Entity_Id) return Boolean;
260          --  Return true if the entity is a subprogram with an appropriate
261          --  profile for the attribute being defined.
262
263          ----------------------
264          -- Has_Good_Profile --
265          ----------------------
266
267          function Has_Good_Profile (Subp : Entity_Id) return Boolean is
268             F              : Entity_Id;
269             Is_Function    : constant Boolean := (TSS_Nam = TSS_Stream_Input);
270             Expected_Ekind : constant array (Boolean) of Entity_Kind :=
271                                (False => E_Procedure, True => E_Function);
272             Typ            : Entity_Id;
273
274          begin
275             if Ekind (Subp) /= Expected_Ekind (Is_Function) then
276                return False;
277             end if;
278
279             F := First_Formal (Subp);
280
281             if No (F)
282               or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
283               or else Designated_Type (Etype (F)) /=
284                                Class_Wide_Type (RTE (RE_Root_Stream_Type))
285             then
286                return False;
287             end if;
288
289             if not Is_Function then
290                Next_Formal (F);
291
292                declare
293                   Expected_Mode : constant array (Boolean) of Entity_Kind :=
294                                     (False => E_In_Parameter,
295                                      True  => E_Out_Parameter);
296                begin
297                   if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
298                      return False;
299                   end if;
300                end;
301
302                Typ := Etype (F);
303
304             else
305                Typ := Etype (Subp);
306             end if;
307
308             return Base_Type (Typ) = Base_Type (Ent)
309               and then No (Next_Formal (F));
310
311          end Has_Good_Profile;
312
313       --  Start of processing for Analyze_Stream_TSS_Definition
314
315       begin
316          FOnly := True;
317
318          if not Is_Type (U_Ent) then
319             Error_Msg_N ("local name must be a subtype", Nam);
320             return;
321          end if;
322
323          Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
324
325          if Present (Pnam) and then Has_Good_Profile (Pnam) then
326             Error_Msg_Sloc := Sloc (Pnam);
327             Error_Msg_Name_1 := Attr;
328             Error_Msg_N ("% attribute already defined #", Nam);
329             return;
330          end if;
331
332          Analyze (Expr);
333
334          if Is_Entity_Name (Expr) then
335             if not Is_Overloaded (Expr) then
336                if Has_Good_Profile (Entity (Expr)) then
337                   Subp := Entity (Expr);
338                end if;
339
340             else
341                Get_First_Interp (Expr, I, It);
342
343                while Present (It.Nam) loop
344                   if Has_Good_Profile (It.Nam) then
345                      Subp := It.Nam;
346                      exit;
347                   end if;
348
349                   Get_Next_Interp (I, It);
350                end loop;
351             end if;
352          end if;
353
354          if Present (Subp) then
355             if Is_Abstract (Subp) then
356                Error_Msg_N ("stream subprogram must not be abstract", Expr);
357                return;
358             end if;
359
360             Set_Entity (Expr, Subp);
361             Set_Etype (Expr, Etype (Subp));
362
363             if TSS_Nam = TSS_Stream_Input then
364                New_Stream_Function (N, U_Ent, Subp, TSS_Nam);
365             else
366                New_Stream_Procedure (N, U_Ent, Subp, TSS_Nam,
367                                      Out_P => Is_Read);
368             end if;
369
370          else
371             Error_Msg_Name_1 := Attr;
372             Error_Msg_N ("incorrect expression for% attribute", Expr);
373          end if;
374       end Analyze_Stream_TSS_Definition;
375
376    --  Start of processing for Analyze_Attribute_Definition_Clause
377
378    begin
379       Analyze (Nam);
380       Ent := Entity (Nam);
381
382       if Rep_Item_Too_Early (Ent, N) then
383          return;
384       end if;
385
386       --  Rep clause applies to full view of incomplete type or private type if
387       --  we have one (if not, this is a premature use of the type). However,
388       --  certain semantic checks need to be done on the specified entity (i.e.
389       --  the private view), so we save it in Ent.
390
391       if Is_Private_Type (Ent)
392         and then Is_Derived_Type (Ent)
393         and then not Is_Tagged_Type (Ent)
394         and then No (Full_View (Ent))
395       then
396          --  If this is a private type whose completion is a derivation from
397          --  another private type, there is no full view, and the attribute
398          --  belongs to the type itself, not its underlying parent.
399
400          U_Ent := Ent;
401
402       elsif Ekind (Ent) = E_Incomplete_Type then
403
404          --  The attribute applies to the full view, set the entity of the
405          --  attribute definition accordingly.
406
407          Ent := Underlying_Type (Ent);
408          U_Ent := Ent;
409          Set_Entity (Nam, Ent);
410
411       else
412          U_Ent := Underlying_Type (Ent);
413       end if;
414
415       --  Complete other routine error checks
416
417       if Etype (Nam) = Any_Type then
418          return;
419
420       elsif Scope (Ent) /= Current_Scope then
421          Error_Msg_N ("entity must be declared in this scope", Nam);
422          return;
423
424       elsif No (U_Ent) then
425          U_Ent := Ent;
426
427       elsif Is_Type (U_Ent)
428         and then not Is_First_Subtype (U_Ent)
429         and then Id /= Attribute_Object_Size
430         and then Id /= Attribute_Value_Size
431         and then not From_At_Mod (N)
432       then
433          Error_Msg_N ("cannot specify attribute for subtype", Nam);
434          return;
435       end if;
436
437       --  Switch on particular attribute
438
439       case Id is
440
441          -------------
442          -- Address --
443          -------------
444
445          --  Address attribute definition clause
446
447          when Attribute_Address => Address : begin
448             Analyze_And_Resolve (Expr, RTE (RE_Address));
449
450             if Present (Address_Clause (U_Ent)) then
451                Error_Msg_N ("address already given for &", Nam);
452
453             --  Case of address clause for subprogram
454
455             elsif Is_Subprogram (U_Ent) then
456                if Has_Homonym (U_Ent) then
457                   Error_Msg_N
458                     ("address clause cannot be given " &
459                      "for overloaded subprogram",
460                      Nam);
461                end if;
462
463                --  For subprograms, all address clauses are permitted,
464                --  and we mark the subprogram as having a deferred freeze
465                --  so that Gigi will not elaborate it too soon.
466
467                --  Above needs more comments, what is too soon about???
468
469                Set_Has_Delayed_Freeze (U_Ent);
470
471             --  Case of address clause for entry
472
473             elsif Ekind (U_Ent) = E_Entry then
474                if Nkind (Parent (N)) = N_Task_Body then
475                   Error_Msg_N
476                     ("entry address must be specified in task spec", Nam);
477                end if;
478
479                --  For entries, we require a constant address
480
481                Check_Constant_Address_Clause (Expr, U_Ent);
482
483                if Is_Task_Type (Scope (U_Ent))
484                  and then Comes_From_Source (Scope (U_Ent))
485                then
486                   Error_Msg_N
487                     ("?entry address declared for entry in task type", N);
488                   Error_Msg_N
489                     ("\?only one task can be declared of this type", N);
490                end if;
491
492                Check_Restriction (No_Obsolescent_Features, N);
493
494                if Warn_On_Obsolescent_Feature then
495                   Error_Msg_N
496                     ("attaching interrupt to task entry is an " &
497                      "obsolescent feature ('R'M 'J.7.1)?", N);
498                   Error_Msg_N
499                     ("\use interrupt procedure instead?", N);
500                end if;
501
502             --  Case of an address clause for a controlled object:
503             --  erroneous execution.
504
505             elsif Is_Controlled (Etype (U_Ent)) then
506                Error_Msg_NE
507                  ("?controlled object& must not be overlaid", Nam, U_Ent);
508                Error_Msg_N
509                  ("\?Program_Error will be raised at run time", Nam);
510                Insert_Action (Declaration_Node (U_Ent),
511                  Make_Raise_Program_Error (Loc,
512                    Reason => PE_Overlaid_Controlled_Object));
513
514             --  Case of address clause for a (non-controlled) object
515
516             elsif
517               Ekind (U_Ent) = E_Variable
518                 or else
519               Ekind (U_Ent) = E_Constant
520             then
521                declare
522                   Expr : constant Node_Id   := Expression (N);
523                   Aent : constant Entity_Id := Address_Aliased_Entity (Expr);
524
525                begin
526                   --  Exported variables cannot have an address clause,
527                   --  because this cancels the effect of the pragma Export
528
529                   if Is_Exported (U_Ent) then
530                      Error_Msg_N
531                        ("cannot export object with address clause", Nam);
532
533                   --  Overlaying controlled objects is erroneous
534
535                   elsif Present (Aent)
536                     and then Is_Controlled (Etype (Aent))
537                   then
538                      Error_Msg_N
539                        ("?controlled object must not be overlaid", Expr);
540                      Error_Msg_N
541                        ("\?Program_Error will be raised at run time", Expr);
542                      Insert_Action (Declaration_Node (U_Ent),
543                        Make_Raise_Program_Error (Loc,
544                          Reason => PE_Overlaid_Controlled_Object));
545
546                   elsif Present (Aent)
547                     and then Ekind (U_Ent) = E_Constant
548                     and then Ekind (Aent) /= E_Constant
549                   then
550                      Error_Msg_N ("constant overlays a variable?", Expr);
551
552                   elsif Present (Renamed_Object (U_Ent)) then
553                      Error_Msg_N
554                        ("address clause not allowed"
555                           & " for a renaming declaration ('R'M 13.1(6))", Nam);
556
557                   --  Imported variables can have an address clause, but then
558                   --  the import is pretty meaningless except to suppress
559                   --  initializations, so we do not need such variables to
560                   --  be statically allocated (and in fact it causes trouble
561                   --  if the address clause is a local value).
562
563                   elsif Is_Imported (U_Ent) then
564                      Set_Is_Statically_Allocated (U_Ent, False);
565                   end if;
566
567                   --  We mark a possible modification of a variable with an
568                   --  address clause, since it is likely aliasing is occurring.
569
570                   Note_Possible_Modification (Nam);
571
572                   --  Here we are checking for explicit overlap of one
573                   --  variable by another, and if we find this, then we
574                   --  mark the overlapped variable as also being aliased.
575
576                   --  First case is where we have an explicit
577
578                   --    for J'Address use K'Address;
579
580                   --  In this case, we mark K as volatile
581
582                   Mark_Aliased_Address_As_Volatile (Expr);
583
584                   --  Second case is where we have a constant whose
585                   --  definition is of the form of an adress as in:
586
587                   --     A : constant Address := K'Address;
588                   --     ...
589                   --     for B'Address use A;
590
591                   --  In this case we also mark K as volatile
592
593                   if Is_Entity_Name (Expr) then
594                      declare
595                         Ent  : constant Entity_Id := Entity (Expr);
596                         Decl : constant Node_Id   := Declaration_Node (Ent);
597
598                      begin
599                         if Ekind (Ent) = E_Constant
600                           and then Nkind (Decl) = N_Object_Declaration
601                           and then Present (Expression (Decl))
602                         then
603                            Mark_Aliased_Address_As_Volatile
604                              (Expression (Decl));
605                         end if;
606                      end;
607                   end if;
608
609                   --  Legality checks on the address clause for initialized
610                   --  objects is deferred until the freeze point, because
611                   --  a subsequent pragma might indicate that the object is
612                   --  imported and thus not initialized.
613
614                   Set_Has_Delayed_Freeze (U_Ent);
615
616                   if Is_Exported (U_Ent) then
617                      Error_Msg_N
618                        ("& cannot be exported if an address clause is given",
619                         Nam);
620                      Error_Msg_N
621                        ("\define and export a variable " &
622                         "that holds its address instead",
623                         Nam);
624                   end if;
625
626                   --  Entity has delayed freeze, so we will generate
627                   --  an alignment check at the freeze point.
628
629                   Set_Check_Address_Alignment
630                     (N, not Range_Checks_Suppressed (U_Ent));
631
632                   --  Kill the size check code, since we are not allocating
633                   --  the variable, it is somewhere else.
634
635                   Kill_Size_Check_Code (U_Ent);
636                end;
637
638             --  Not a valid entity for an address clause
639
640             else
641                Error_Msg_N ("address cannot be given for &", Nam);
642             end if;
643          end Address;
644
645          ---------------
646          -- Alignment --
647          ---------------
648
649          --  Alignment attribute definition clause
650
651          when Attribute_Alignment => Alignment_Block : declare
652             Align : constant Uint := Get_Alignment_Value (Expr);
653
654          begin
655             FOnly := True;
656
657             if not Is_Type (U_Ent)
658               and then Ekind (U_Ent) /= E_Variable
659               and then Ekind (U_Ent) /= E_Constant
660             then
661                Error_Msg_N ("alignment cannot be given for &", Nam);
662
663             elsif Has_Alignment_Clause (U_Ent) then
664                Error_Msg_Sloc := Sloc (Alignment_Clause (U_Ent));
665                Error_Msg_N ("alignment clause previously given#", N);
666
667             elsif Align /= No_Uint then
668                Set_Has_Alignment_Clause (U_Ent);
669                Set_Alignment            (U_Ent, Align);
670             end if;
671          end Alignment_Block;
672
673          ---------------
674          -- Bit_Order --
675          ---------------
676
677          --  Bit_Order attribute definition clause
678
679          when Attribute_Bit_Order => Bit_Order : declare
680          begin
681             if not Is_Record_Type (U_Ent) then
682                Error_Msg_N
683                  ("Bit_Order can only be defined for record type", Nam);
684
685             else
686                Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
687
688                if Etype (Expr) = Any_Type then
689                   return;
690
691                elsif not Is_Static_Expression (Expr) then
692                   Flag_Non_Static_Expr
693                     ("Bit_Order requires static expression!", Expr);
694
695                else
696                   if (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
697                      Set_Reverse_Bit_Order (U_Ent, True);
698                   end if;
699                end if;
700             end if;
701          end Bit_Order;
702
703          --------------------
704          -- Component_Size --
705          --------------------
706
707          --  Component_Size attribute definition clause
708
709          when Attribute_Component_Size => Component_Size_Case : declare
710             Csize    : constant Uint := Static_Integer (Expr);
711             Btype    : Entity_Id;
712             Biased   : Boolean;
713             New_Ctyp : Entity_Id;
714             Decl     : Node_Id;
715
716          begin
717             if not Is_Array_Type (U_Ent) then
718                Error_Msg_N ("component size requires array type", Nam);
719                return;
720             end if;
721
722             Btype := Base_Type (U_Ent);
723
724             if Has_Component_Size_Clause (Btype) then
725                Error_Msg_N
726                  ("component size clase for& previously given", Nam);
727
728             elsif Csize /= No_Uint then
729                Check_Size (Expr, Component_Type (Btype), Csize, Biased);
730
731                if Has_Aliased_Components (Btype)
732                  and then Csize < 32
733                  and then Csize /= 8
734                  and then Csize /= 16
735                then
736                   Error_Msg_N
737                     ("component size incorrect for aliased components", N);
738                   return;
739                end if;
740
741                --  For the biased case, build a declaration for a subtype
742                --  that will be used to represent the biased subtype that
743                --  reflects the biased representation of components. We need
744                --  this subtype to get proper conversions on referencing
745                --  elements of the array.
746
747                if Biased then
748                   New_Ctyp :=
749                     Make_Defining_Identifier (Loc,
750                       Chars => New_External_Name (Chars (U_Ent), 'C', 0, 'T'));
751
752                   Decl :=
753                     Make_Subtype_Declaration (Loc,
754                       Defining_Identifier => New_Ctyp,
755                       Subtype_Indication  =>
756                         New_Occurrence_Of (Component_Type (Btype), Loc));
757
758                   Set_Parent (Decl, N);
759                   Analyze (Decl, Suppress => All_Checks);
760
761                   Set_Has_Delayed_Freeze        (New_Ctyp, False);
762                   Set_Esize                     (New_Ctyp, Csize);
763                   Set_RM_Size                   (New_Ctyp, Csize);
764                   Init_Alignment                (New_Ctyp);
765                   Set_Has_Biased_Representation (New_Ctyp, True);
766                   Set_Is_Itype                  (New_Ctyp, True);
767                   Set_Associated_Node_For_Itype (New_Ctyp, U_Ent);
768
769                   Set_Component_Type (Btype, New_Ctyp);
770                end if;
771
772                Set_Component_Size            (Btype, Csize);
773                Set_Has_Component_Size_Clause (Btype, True);
774                Set_Has_Non_Standard_Rep      (Btype, True);
775             end if;
776          end Component_Size_Case;
777
778          ------------------
779          -- External_Tag --
780          ------------------
781
782          when Attribute_External_Tag => External_Tag :
783          begin
784             if not Is_Tagged_Type (U_Ent) then
785                Error_Msg_N ("should be a tagged type", Nam);
786             end if;
787
788             Analyze_And_Resolve (Expr, Standard_String);
789
790             if not Is_Static_Expression (Expr) then
791                Flag_Non_Static_Expr
792                  ("static string required for tag name!", Nam);
793             end if;
794
795             Set_Has_External_Tag_Rep_Clause (U_Ent);
796          end External_Tag;
797
798          -----------
799          -- Input --
800          -----------
801
802          when Attribute_Input =>
803             Analyze_Stream_TSS_Definition (TSS_Stream_Input);
804             Set_Has_Specified_Stream_Input (Ent);
805
806          -------------------
807          -- Machine_Radix --
808          -------------------
809
810          --  Machine radix attribute definition clause
811
812          when Attribute_Machine_Radix => Machine_Radix : declare
813             Radix : constant Uint := Static_Integer (Expr);
814
815          begin
816             if not Is_Decimal_Fixed_Point_Type (U_Ent) then
817                Error_Msg_N ("decimal fixed-point type expected for &", Nam);
818
819             elsif Has_Machine_Radix_Clause (U_Ent) then
820                Error_Msg_Sloc := Sloc (Alignment_Clause (U_Ent));
821                Error_Msg_N ("machine radix clause previously given#", N);
822
823             elsif Radix /= No_Uint then
824                Set_Has_Machine_Radix_Clause (U_Ent);
825                Set_Has_Non_Standard_Rep (Base_Type (U_Ent));
826
827                if Radix = 2 then
828                   null;
829                elsif Radix = 10 then
830                   Set_Machine_Radix_10 (U_Ent);
831                else
832                   Error_Msg_N ("machine radix value must be 2 or 10", Expr);
833                end if;
834             end if;
835          end Machine_Radix;
836
837          -----------------
838          -- Object_Size --
839          -----------------
840
841          --  Object_Size attribute definition clause
842
843          when Attribute_Object_Size => Object_Size : declare
844             Size   : constant Uint := Static_Integer (Expr);
845             Biased : Boolean;
846
847          begin
848             if not Is_Type (U_Ent) then
849                Error_Msg_N ("Object_Size cannot be given for &", Nam);
850
851             elsif Has_Object_Size_Clause (U_Ent) then
852                Error_Msg_N ("Object_Size already given for &", Nam);
853
854             else
855                Check_Size (Expr, U_Ent, Size, Biased);
856
857                if Size /= 8
858                     and then
859                   Size /= 16
860                     and then
861                   Size /= 32
862                     and then
863                   UI_Mod (Size, 64) /= 0
864                then
865                   Error_Msg_N
866                     ("Object_Size must be 8, 16, 32, or multiple of 64",
867                      Expr);
868                end if;
869
870                Set_Esize (U_Ent, Size);
871                Set_Has_Object_Size_Clause (U_Ent);
872                Alignment_Check_For_Esize_Change (U_Ent);
873             end if;
874          end Object_Size;
875
876          ------------
877          -- Output --
878          ------------
879
880          when Attribute_Output =>
881             Analyze_Stream_TSS_Definition (TSS_Stream_Output);
882             Set_Has_Specified_Stream_Output (Ent);
883
884          ----------
885          -- Read --
886          ----------
887
888          when Attribute_Read =>
889             Analyze_Stream_TSS_Definition (TSS_Stream_Read);
890             Set_Has_Specified_Stream_Read (Ent);
891
892          ----------
893          -- Size --
894          ----------
895
896          --  Size attribute definition clause
897
898          when Attribute_Size => Size : declare
899             Size   : constant Uint := Static_Integer (Expr);
900             Etyp   : Entity_Id;
901             Biased : Boolean;
902
903          begin
904             FOnly := True;
905
906             if Has_Size_Clause (U_Ent) then
907                Error_Msg_N ("size already given for &", Nam);
908
909             elsif not Is_Type (U_Ent)
910               and then Ekind (U_Ent) /= E_Variable
911               and then Ekind (U_Ent) /= E_Constant
912             then
913                Error_Msg_N ("size cannot be given for &", Nam);
914
915             elsif Is_Array_Type (U_Ent)
916               and then not Is_Constrained (U_Ent)
917             then
918                Error_Msg_N
919                  ("size cannot be given for unconstrained array", Nam);
920
921             elsif Size /= No_Uint then
922                if Is_Type (U_Ent) then
923                   Etyp := U_Ent;
924                else
925                   Etyp := Etype (U_Ent);
926                end if;
927
928                --  Check size, note that Gigi is in charge of checking
929                --  that the size of an array or record type is OK. Also
930                --  we do not check the size in the ordinary fixed-point
931                --  case, since it is too early to do so (there may be a
932                --  subsequent small clause that affects the size). We can
933                --  check the size if a small clause has already been given.
934
935                if not Is_Ordinary_Fixed_Point_Type (U_Ent)
936                  or else Has_Small_Clause (U_Ent)
937                then
938                   Check_Size (Expr, Etyp, Size, Biased);
939                   Set_Has_Biased_Representation (U_Ent, Biased);
940                end if;
941
942                --  For types set RM_Size and Esize if possible
943
944                if Is_Type (U_Ent) then
945                   Set_RM_Size (U_Ent, Size);
946
947                   --  For scalar types, increase Object_Size to power of 2,
948                   --  but not less than a storage unit in any case (i.e.,
949                   --  normally this means it will be byte addressable).
950
951                   if Is_Scalar_Type (U_Ent) then
952                      if Size <= System_Storage_Unit then
953                         Init_Esize (U_Ent, System_Storage_Unit);
954                      elsif Size <= 16 then
955                         Init_Esize (U_Ent, 16);
956                      elsif Size <= 32 then
957                         Init_Esize (U_Ent, 32);
958                      else
959                         Set_Esize  (U_Ent, (Size + 63) / 64 * 64);
960                      end if;
961
962                   --  For all other types, object size = value size. The
963                   --  backend will adjust as needed.
964
965                   else
966                      Set_Esize (U_Ent, Size);
967                   end if;
968
969                   Alignment_Check_For_Esize_Change (U_Ent);
970
971                --  For objects, set Esize only
972
973                else
974                   if Is_Elementary_Type (Etyp) then
975                      if Size /= System_Storage_Unit
976                           and then
977                         Size /= System_Storage_Unit * 2
978                           and then
979                         Size /= System_Storage_Unit * 4
980                            and then
981                         Size /= System_Storage_Unit * 8
982                      then
983                         Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
984                         Error_Msg_N
985                           ("size for primitive object must be a power of 2"
986                             & " and at least ^", N);
987                      end if;
988                   end if;
989
990                   Set_Esize (U_Ent, Size);
991                end if;
992
993                Set_Has_Size_Clause (U_Ent);
994             end if;
995          end Size;
996
997          -----------
998          -- Small --
999          -----------
1000
1001          --  Small attribute definition clause
1002
1003          when Attribute_Small => Small : declare
1004             Implicit_Base : constant Entity_Id := Base_Type (U_Ent);
1005             Small         : Ureal;
1006
1007          begin
1008             Analyze_And_Resolve (Expr, Any_Real);
1009
1010             if Etype (Expr) = Any_Type then
1011                return;
1012
1013             elsif not Is_Static_Expression (Expr) then
1014                Flag_Non_Static_Expr
1015                  ("small requires static expression!", Expr);
1016                return;
1017
1018             else
1019                Small := Expr_Value_R (Expr);
1020
1021                if Small <= Ureal_0 then
1022                   Error_Msg_N ("small value must be greater than zero", Expr);
1023                   return;
1024                end if;
1025
1026             end if;
1027
1028             if not Is_Ordinary_Fixed_Point_Type (U_Ent) then
1029                Error_Msg_N
1030                  ("small requires an ordinary fixed point type", Nam);
1031
1032             elsif Has_Small_Clause (U_Ent) then
1033                Error_Msg_N ("small already given for &", Nam);
1034
1035             elsif Small > Delta_Value (U_Ent) then
1036                Error_Msg_N
1037                  ("small value must not be greater then delta value", Nam);
1038
1039             else
1040                Set_Small_Value (U_Ent, Small);
1041                Set_Small_Value (Implicit_Base, Small);
1042                Set_Has_Small_Clause (U_Ent);
1043                Set_Has_Small_Clause (Implicit_Base);
1044                Set_Has_Non_Standard_Rep (Implicit_Base);
1045             end if;
1046          end Small;
1047
1048          ------------------
1049          -- Storage_Size --
1050          ------------------
1051
1052          --  Storage_Size attribute definition clause
1053
1054          when Attribute_Storage_Size => Storage_Size : declare
1055             Btype : constant Entity_Id := Base_Type (U_Ent);
1056             Sprag : Node_Id;
1057
1058          begin
1059             if Is_Task_Type (U_Ent) then
1060                Check_Restriction (No_Obsolescent_Features, N);
1061
1062                if Warn_On_Obsolescent_Feature then
1063                   Error_Msg_N
1064                     ("storage size clause for task is an " &
1065                      "obsolescent feature ('R'M 'J.9)?", N);
1066                   Error_Msg_N
1067                     ("\use Storage_Size pragma instead?", N);
1068                end if;
1069
1070                FOnly := True;
1071             end if;
1072
1073             if not Is_Access_Type (U_Ent)
1074               and then Ekind (U_Ent) /= E_Task_Type
1075             then
1076                Error_Msg_N ("storage size cannot be given for &", Nam);
1077
1078             elsif Is_Access_Type (U_Ent) and Is_Derived_Type (U_Ent) then
1079                Error_Msg_N
1080                  ("storage size cannot be given for a derived access type",
1081                   Nam);
1082
1083             elsif Has_Storage_Size_Clause (Btype) then
1084                Error_Msg_N ("storage size already given for &", Nam);
1085
1086             else
1087                Analyze_And_Resolve (Expr, Any_Integer);
1088
1089                if Is_Access_Type (U_Ent) then
1090
1091                   if Present (Associated_Storage_Pool (U_Ent)) then
1092                      Error_Msg_N ("storage pool already given for &", Nam);
1093                      return;
1094                   end if;
1095
1096                   if Compile_Time_Known_Value (Expr)
1097                     and then Expr_Value (Expr) = 0
1098                   then
1099                      Set_No_Pool_Assigned (Btype);
1100                   end if;
1101
1102                else -- Is_Task_Type (U_Ent)
1103                   Sprag := Get_Rep_Pragma (Btype, Name_Storage_Size);
1104
1105                   if Present (Sprag) then
1106                      Error_Msg_Sloc := Sloc (Sprag);
1107                      Error_Msg_N
1108                        ("Storage_Size already specified#", Nam);
1109                      return;
1110                   end if;
1111                end if;
1112
1113                Set_Has_Storage_Size_Clause (Btype);
1114             end if;
1115          end Storage_Size;
1116
1117          ------------------
1118          -- Storage_Pool --
1119          ------------------
1120
1121          --  Storage_Pool attribute definition clause
1122
1123          when Attribute_Storage_Pool => Storage_Pool : declare
1124             Pool : Entity_Id;
1125             T    : Entity_Id;
1126
1127          begin
1128             if Ekind (U_Ent) /= E_Access_Type
1129               and then Ekind (U_Ent) /= E_General_Access_Type
1130             then
1131                Error_Msg_N (
1132                  "storage pool can only be given for access types", Nam);
1133                return;
1134
1135             elsif Is_Derived_Type (U_Ent) then
1136                Error_Msg_N
1137                  ("storage pool cannot be given for a derived access type",
1138                   Nam);
1139
1140             elsif Has_Storage_Size_Clause (U_Ent) then
1141                Error_Msg_N ("storage size already given for &", Nam);
1142                return;
1143
1144             elsif Present (Associated_Storage_Pool (U_Ent)) then
1145                Error_Msg_N ("storage pool already given for &", Nam);
1146                return;
1147             end if;
1148
1149             Analyze_And_Resolve
1150               (Expr, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
1151
1152             if Nkind (Expr) = N_Type_Conversion then
1153                T := Etype (Expression (Expr));
1154             else
1155                T := Etype (Expr);
1156             end if;
1157
1158             --  The Stack_Bounded_Pool is used internally for implementing
1159             --  access types with a Storage_Size. Since it only work
1160             --  properly when used on one specific type, we need to check
1161             --  that it is not highjacked improperly:
1162             --    type T is access Integer;
1163             --    for T'Storage_Size use n;
1164             --    type Q is access Float;
1165             --    for Q'Storage_Size use T'Storage_Size; -- incorrect
1166
1167             if Base_Type (T) = RTE (RE_Stack_Bounded_Pool) then
1168                Error_Msg_N ("non-sharable internal Pool", Expr);
1169                return;
1170             end if;
1171
1172             --  If the argument is a name that is not an entity name, then
1173             --  we construct a renaming operation to define an entity of
1174             --  type storage pool.
1175
1176             if not Is_Entity_Name (Expr)
1177               and then Is_Object_Reference (Expr)
1178             then
1179                Pool :=
1180                  Make_Defining_Identifier (Loc,
1181                    Chars => New_Internal_Name ('P'));
1182
1183                declare
1184                   Rnode : constant Node_Id :=
1185                             Make_Object_Renaming_Declaration (Loc,
1186                               Defining_Identifier => Pool,
1187                               Subtype_Mark        =>
1188                                 New_Occurrence_Of (Etype (Expr), Loc),
1189                               Name => Expr);
1190
1191                begin
1192                   Insert_Before (N, Rnode);
1193                   Analyze (Rnode);
1194                   Set_Associated_Storage_Pool (U_Ent, Pool);
1195                end;
1196
1197             elsif Is_Entity_Name (Expr) then
1198                Pool := Entity (Expr);
1199
1200                --  If pool is a renamed object, get original one. This can
1201                --  happen with an explicit renaming, and within instances.
1202
1203                while Present (Renamed_Object (Pool))
1204                  and then Is_Entity_Name (Renamed_Object (Pool))
1205                loop
1206                   Pool := Entity (Renamed_Object (Pool));
1207                end loop;
1208
1209                if Present (Renamed_Object (Pool))
1210                  and then Nkind (Renamed_Object (Pool)) = N_Type_Conversion
1211                  and then Is_Entity_Name (Expression (Renamed_Object (Pool)))
1212                then
1213                   Pool := Entity (Expression (Renamed_Object (Pool)));
1214                end if;
1215
1216                Set_Associated_Storage_Pool (U_Ent, Pool);
1217
1218             elsif Nkind (Expr) = N_Type_Conversion
1219               and then Is_Entity_Name (Expression (Expr))
1220               and then Nkind (Original_Node (Expr)) = N_Attribute_Reference
1221             then
1222                Pool := Entity (Expression (Expr));
1223                Set_Associated_Storage_Pool (U_Ent, Pool);
1224
1225             else
1226                Error_Msg_N ("incorrect reference to a Storage Pool", Expr);
1227                return;
1228             end if;
1229          end Storage_Pool;
1230
1231          -----------------
1232          -- Stream_Size --
1233          -----------------
1234
1235          when Attribute_Stream_Size => Stream_Size : declare
1236             Size : constant Uint := Static_Integer (Expr);
1237
1238          begin
1239             if Has_Stream_Size_Clause (U_Ent) then
1240                Error_Msg_N ("Stream_Size already given for &", Nam);
1241
1242             elsif Is_Elementary_Type (U_Ent) then
1243                if Size /= System_Storage_Unit
1244                     and then
1245                   Size /= System_Storage_Unit * 2
1246                     and then
1247                   Size /= System_Storage_Unit * 4
1248                      and then
1249                   Size /= System_Storage_Unit * 8
1250                then
1251                   Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
1252                   Error_Msg_N
1253                     ("stream size for elementary type must be a"
1254                        & " power of 2 and at least ^", N);
1255
1256                elsif RM_Size (U_Ent) > Size then
1257                   Error_Msg_Uint_1 := RM_Size (U_Ent);
1258                   Error_Msg_N
1259                     ("stream size for elementary type must be a"
1260                        & " power of 2 and at least ^", N);
1261                end if;
1262
1263                Set_Has_Stream_Size_Clause (U_Ent);
1264
1265             else
1266                Error_Msg_N ("Stream_Size cannot be given for &", Nam);
1267             end if;
1268          end Stream_Size;
1269
1270          ----------------
1271          -- Value_Size --
1272          ----------------
1273
1274          --  Value_Size attribute definition clause
1275
1276          when Attribute_Value_Size => Value_Size : declare
1277             Size   : constant Uint := Static_Integer (Expr);
1278             Biased : Boolean;
1279
1280          begin
1281             if not Is_Type (U_Ent) then
1282                Error_Msg_N ("Value_Size cannot be given for &", Nam);
1283
1284             elsif Present
1285                    (Get_Attribute_Definition_Clause
1286                      (U_Ent, Attribute_Value_Size))
1287             then
1288                Error_Msg_N ("Value_Size already given for &", Nam);
1289
1290             else
1291                if Is_Elementary_Type (U_Ent) then
1292                   Check_Size (Expr, U_Ent, Size, Biased);
1293                   Set_Has_Biased_Representation (U_Ent, Biased);
1294                end if;
1295
1296                Set_RM_Size (U_Ent, Size);
1297             end if;
1298          end Value_Size;
1299
1300          -----------
1301          -- Write --
1302          -----------
1303
1304          when Attribute_Write =>
1305             Analyze_Stream_TSS_Definition (TSS_Stream_Write);
1306             Set_Has_Specified_Stream_Write (Ent);
1307
1308          --  All other attributes cannot be set
1309
1310          when others =>
1311             Error_Msg_N
1312               ("attribute& cannot be set with definition clause", N);
1313       end case;
1314
1315       --  The test for the type being frozen must be performed after
1316       --  any expression the clause has been analyzed since the expression
1317       --  itself might cause freezing that makes the clause illegal.
1318
1319       if Rep_Item_Too_Late (U_Ent, N, FOnly) then
1320          return;
1321       end if;
1322    end Analyze_Attribute_Definition_Clause;
1323
1324    ----------------------------
1325    -- Analyze_Code_Statement --
1326    ----------------------------
1327
1328    procedure Analyze_Code_Statement (N : Node_Id) is
1329       HSS   : constant Node_Id   := Parent (N);
1330       SBody : constant Node_Id   := Parent (HSS);
1331       Subp  : constant Entity_Id := Current_Scope;
1332       Stmt  : Node_Id;
1333       Decl  : Node_Id;
1334       StmtO : Node_Id;
1335       DeclO : Node_Id;
1336
1337    begin
1338       --  Analyze and check we get right type, note that this implements the
1339       --  requirement (RM 13.8(1)) that Machine_Code be with'ed, since that
1340       --  is the only way that Asm_Insn could possibly be visible.
1341
1342       Analyze_And_Resolve (Expression (N));
1343
1344       if Etype (Expression (N)) = Any_Type then
1345          return;
1346       elsif Etype (Expression (N)) /= RTE (RE_Asm_Insn) then
1347          Error_Msg_N ("incorrect type for code statement", N);
1348          return;
1349       end if;
1350
1351       --  Make sure we appear in the handled statement sequence of a
1352       --  subprogram (RM 13.8(3)).
1353
1354       if Nkind (HSS) /= N_Handled_Sequence_Of_Statements
1355         or else Nkind (SBody) /= N_Subprogram_Body
1356       then
1357          Error_Msg_N
1358            ("code statement can only appear in body of subprogram", N);
1359          return;
1360       end if;
1361
1362       --  Do remaining checks (RM 13.8(3)) if not already done
1363
1364       if not Is_Machine_Code_Subprogram (Subp) then
1365          Set_Is_Machine_Code_Subprogram (Subp);
1366
1367          --  No exception handlers allowed
1368
1369          if Present (Exception_Handlers (HSS)) then
1370             Error_Msg_N
1371               ("exception handlers not permitted in machine code subprogram",
1372                First (Exception_Handlers (HSS)));
1373          end if;
1374
1375          --  No declarations other than use clauses and pragmas (we allow
1376          --  certain internally generated declarations as well).
1377
1378          Decl := First (Declarations (SBody));
1379          while Present (Decl) loop
1380             DeclO := Original_Node (Decl);
1381             if Comes_From_Source (DeclO)
1382               and then Nkind (DeclO) /= N_Pragma
1383               and then Nkind (DeclO) /= N_Use_Package_Clause
1384               and then Nkind (DeclO) /= N_Use_Type_Clause
1385               and then Nkind (DeclO) /= N_Implicit_Label_Declaration
1386             then
1387                Error_Msg_N
1388                  ("this declaration not allowed in machine code subprogram",
1389                   DeclO);
1390             end if;
1391
1392             Next (Decl);
1393          end loop;
1394
1395          --  No statements other than code statements, pragmas, and labels.
1396          --  Again we allow certain internally generated statements.
1397
1398          Stmt := First (Statements (HSS));
1399          while Present (Stmt) loop
1400             StmtO := Original_Node (Stmt);
1401             if Comes_From_Source (StmtO)
1402               and then Nkind (StmtO) /= N_Pragma
1403               and then Nkind (StmtO) /= N_Label
1404               and then Nkind (StmtO) /= N_Code_Statement
1405             then
1406                Error_Msg_N
1407                  ("this statement is not allowed in machine code subprogram",
1408                   StmtO);
1409             end if;
1410
1411             Next (Stmt);
1412          end loop;
1413       end if;
1414    end Analyze_Code_Statement;
1415
1416    -----------------------------------------------
1417    -- Analyze_Enumeration_Representation_Clause --
1418    -----------------------------------------------
1419
1420    procedure Analyze_Enumeration_Representation_Clause (N : Node_Id) is
1421       Ident    : constant Node_Id    := Identifier (N);
1422       Aggr     : constant Node_Id    := Array_Aggregate (N);
1423       Enumtype : Entity_Id;
1424       Elit     : Entity_Id;
1425       Expr     : Node_Id;
1426       Assoc    : Node_Id;
1427       Choice   : Node_Id;
1428       Val      : Uint;
1429       Err      : Boolean := False;
1430
1431       Lo  : constant Uint := Expr_Value (Type_Low_Bound (Universal_Integer));
1432       Hi  : constant Uint := Expr_Value (Type_High_Bound (Universal_Integer));
1433       Min : Uint;
1434       Max : Uint;
1435
1436    begin
1437       --  First some basic error checks
1438
1439       Find_Type (Ident);
1440       Enumtype := Entity (Ident);
1441
1442       if Enumtype = Any_Type
1443         or else Rep_Item_Too_Early (Enumtype, N)
1444       then
1445          return;
1446       else
1447          Enumtype := Underlying_Type (Enumtype);
1448       end if;
1449
1450       if not Is_Enumeration_Type (Enumtype) then
1451          Error_Msg_NE
1452            ("enumeration type required, found}",
1453             Ident, First_Subtype (Enumtype));
1454          return;
1455       end if;
1456
1457       --  Ignore rep clause on generic actual type. This will already have
1458       --  been flagged on the template as an error, and this is the safest
1459       --  way to ensure we don't get a junk cascaded message in the instance.
1460
1461       if Is_Generic_Actual_Type (Enumtype) then
1462          return;
1463
1464       --  Type must be in current scope
1465
1466       elsif Scope (Enumtype) /= Current_Scope then
1467          Error_Msg_N ("type must be declared in this scope", Ident);
1468          return;
1469
1470       --  Type must be a first subtype
1471
1472       elsif not Is_First_Subtype (Enumtype) then
1473          Error_Msg_N ("cannot give enumeration rep clause for subtype", N);
1474          return;
1475
1476       --  Ignore duplicate rep clause
1477
1478       elsif Has_Enumeration_Rep_Clause (Enumtype) then
1479          Error_Msg_N ("duplicate enumeration rep clause ignored", N);
1480          return;
1481
1482       --  Don't allow rep clause for standard [wide_[wide_]]character
1483
1484       elsif Root_Type (Enumtype) = Standard_Character
1485         or else Root_Type (Enumtype) = Standard_Wide_Character
1486         or else Root_Type (Enumtype) = Standard_Wide_Wide_Character
1487       then
1488          Error_Msg_N ("enumeration rep clause not allowed for this type", N);
1489          return;
1490
1491       --  Check that the expression is a proper aggregate (no parentheses)
1492
1493       elsif Paren_Count (Aggr) /= 0 then
1494          Error_Msg
1495            ("extra parentheses surrounding aggregate not allowed",
1496             First_Sloc (Aggr));
1497          return;
1498
1499       --  All tests passed, so set rep clause in place
1500
1501       else
1502          Set_Has_Enumeration_Rep_Clause (Enumtype);
1503          Set_Has_Enumeration_Rep_Clause (Base_Type (Enumtype));
1504       end if;
1505
1506       --  Now we process the aggregate. Note that we don't use the normal
1507       --  aggregate code for this purpose, because we don't want any of the
1508       --  normal expansion activities, and a number of special semantic
1509       --  rules apply (including the component type being any integer type)
1510
1511       Elit := First_Literal (Enumtype);
1512
1513       --  First the positional entries if any
1514
1515       if Present (Expressions (Aggr)) then
1516          Expr := First (Expressions (Aggr));
1517          while Present (Expr) loop
1518             if No (Elit) then
1519                Error_Msg_N ("too many entries in aggregate", Expr);
1520                return;
1521             end if;
1522
1523             Val := Static_Integer (Expr);
1524
1525             --  Err signals that we found some incorrect entries processing
1526             --  the list. The final checks for completeness and ordering are
1527             --  skipped in this case.
1528
1529             if Val = No_Uint then
1530                Err := True;
1531             elsif Val < Lo or else Hi < Val then
1532                Error_Msg_N ("value outside permitted range", Expr);
1533                Err := True;
1534             end if;
1535
1536             Set_Enumeration_Rep (Elit, Val);
1537             Set_Enumeration_Rep_Expr (Elit, Expr);
1538             Next (Expr);
1539             Next (Elit);
1540          end loop;
1541       end if;
1542
1543       --  Now process the named entries if present
1544
1545       if Present (Component_Associations (Aggr)) then
1546          Assoc := First (Component_Associations (Aggr));
1547          while Present (Assoc) loop
1548             Choice := First (Choices (Assoc));
1549
1550             if Present (Next (Choice)) then
1551                Error_Msg_N
1552                  ("multiple choice not allowed here", Next (Choice));
1553                Err := True;
1554             end if;
1555
1556             if Nkind (Choice) = N_Others_Choice then
1557                Error_Msg_N ("others choice not allowed here", Choice);
1558                Err := True;
1559
1560             elsif Nkind (Choice) = N_Range then
1561                --  ??? should allow zero/one element range here
1562                Error_Msg_N ("range not allowed here", Choice);
1563                Err := True;
1564
1565             else
1566                Analyze_And_Resolve (Choice, Enumtype);
1567
1568                if Is_Entity_Name (Choice)
1569                  and then Is_Type (Entity (Choice))
1570                then
1571                   Error_Msg_N ("subtype name not allowed here", Choice);
1572                   Err := True;
1573                   --  ??? should allow static subtype with zero/one entry
1574
1575                elsif Etype (Choice) = Base_Type (Enumtype) then
1576                   if not Is_Static_Expression (Choice) then
1577                      Flag_Non_Static_Expr
1578                        ("non-static expression used for choice!", Choice);
1579                      Err := True;
1580
1581                   else
1582                      Elit := Expr_Value_E (Choice);
1583
1584                      if Present (Enumeration_Rep_Expr (Elit)) then
1585                         Error_Msg_Sloc := Sloc (Enumeration_Rep_Expr (Elit));
1586                         Error_Msg_NE
1587                           ("representation for& previously given#",
1588                            Choice, Elit);
1589                         Err := True;
1590                      end if;
1591
1592                      Set_Enumeration_Rep_Expr (Elit, Choice);
1593
1594                      Expr := Expression (Assoc);
1595                      Val := Static_Integer (Expr);
1596
1597                      if Val = No_Uint then
1598                         Err := True;
1599
1600                      elsif Val < Lo or else Hi < Val then
1601                         Error_Msg_N ("value outside permitted range", Expr);
1602                         Err := True;
1603                      end if;
1604
1605                      Set_Enumeration_Rep (Elit, Val);
1606                   end if;
1607                end if;
1608             end if;
1609
1610             Next (Assoc);
1611          end loop;
1612       end if;
1613
1614       --  Aggregate is fully processed. Now we check that a full set of
1615       --  representations was given, and that they are in range and in order.
1616       --  These checks are only done if no other errors occurred.
1617
1618       if not Err then
1619          Min  := No_Uint;
1620          Max  := No_Uint;
1621
1622          Elit := First_Literal (Enumtype);
1623          while Present (Elit) loop
1624             if No (Enumeration_Rep_Expr (Elit)) then
1625                Error_Msg_NE ("missing representation for&!", N, Elit);
1626
1627             else
1628                Val := Enumeration_Rep (Elit);
1629
1630                if Min = No_Uint then
1631                   Min := Val;
1632                end if;
1633
1634                if Val /= No_Uint then
1635                   if Max /= No_Uint and then Val <= Max then
1636                      Error_Msg_NE
1637                        ("enumeration value for& not ordered!",
1638                                        Enumeration_Rep_Expr (Elit), Elit);
1639                   end if;
1640
1641                   Max := Val;
1642                end if;
1643
1644                --  If there is at least one literal whose representation
1645                --  is not equal to the Pos value, then note that this
1646                --  enumeration type has a non-standard representation.
1647
1648                if Val /= Enumeration_Pos (Elit) then
1649                   Set_Has_Non_Standard_Rep (Base_Type (Enumtype));
1650                end if;
1651             end if;
1652
1653             Next (Elit);
1654          end loop;
1655
1656          --  Now set proper size information
1657
1658          declare
1659             Minsize : Uint := UI_From_Int (Minimum_Size (Enumtype));
1660
1661          begin
1662             if Has_Size_Clause (Enumtype) then
1663                if Esize (Enumtype) >= Minsize then
1664                   null;
1665
1666                else
1667                   Minsize :=
1668                     UI_From_Int (Minimum_Size (Enumtype, Biased => True));
1669
1670                   if Esize (Enumtype) < Minsize then
1671                      Error_Msg_N ("previously given size is too small", N);
1672
1673                   else
1674                      Set_Has_Biased_Representation (Enumtype);
1675                   end if;
1676                end if;
1677
1678             else
1679                Set_RM_Size    (Enumtype, Minsize);
1680                Set_Enum_Esize (Enumtype);
1681             end if;
1682
1683             Set_RM_Size   (Base_Type (Enumtype), RM_Size   (Enumtype));
1684             Set_Esize     (Base_Type (Enumtype), Esize     (Enumtype));
1685             Set_Alignment (Base_Type (Enumtype), Alignment (Enumtype));
1686          end;
1687       end if;
1688
1689       --  We repeat the too late test in case it froze itself!
1690
1691       if Rep_Item_Too_Late (Enumtype, N) then
1692          null;
1693       end if;
1694    end Analyze_Enumeration_Representation_Clause;
1695
1696    ----------------------------
1697    -- Analyze_Free_Statement --
1698    ----------------------------
1699
1700    procedure Analyze_Free_Statement (N : Node_Id) is
1701    begin
1702       Analyze (Expression (N));
1703    end Analyze_Free_Statement;
1704
1705    ------------------------------------------
1706    -- Analyze_Record_Representation_Clause --
1707    ------------------------------------------
1708
1709    procedure Analyze_Record_Representation_Clause (N : Node_Id) is
1710       Loc     : constant Source_Ptr := Sloc (N);
1711       Ident   : constant Node_Id    := Identifier (N);
1712       Rectype : Entity_Id;
1713       Fent    : Entity_Id;
1714       CC      : Node_Id;
1715       Posit   : Uint;
1716       Fbit    : Uint;
1717       Lbit    : Uint;
1718       Hbit    : Uint := Uint_0;
1719       Comp    : Entity_Id;
1720       Ocomp   : Entity_Id;
1721       Biased  : Boolean;
1722
1723       Max_Bit_So_Far : Uint;
1724       --  Records the maximum bit position so far. If all field positions
1725       --  are monotonically increasing, then we can skip the circuit for
1726       --  checking for overlap, since no overlap is possible.
1727
1728       Overlap_Check_Required : Boolean;
1729       --  Used to keep track of whether or not an overlap check is required
1730
1731       Ccount : Natural := 0;
1732       --  Number of component clauses in record rep clause
1733
1734    begin
1735       Find_Type (Ident);
1736       Rectype := Entity (Ident);
1737
1738       if Rectype = Any_Type
1739         or else Rep_Item_Too_Early (Rectype, N)
1740       then
1741          return;
1742       else
1743          Rectype := Underlying_Type (Rectype);
1744       end if;
1745
1746       --  First some basic error checks
1747
1748       if not Is_Record_Type (Rectype) then
1749          Error_Msg_NE
1750            ("record type required, found}", Ident, First_Subtype (Rectype));
1751          return;
1752
1753       elsif Is_Unchecked_Union (Rectype) then
1754          Error_Msg_N
1755            ("record rep clause not allowed for Unchecked_Union", N);
1756
1757       elsif Scope (Rectype) /= Current_Scope then
1758          Error_Msg_N ("type must be declared in this scope", N);
1759          return;
1760
1761       elsif not Is_First_Subtype (Rectype) then
1762          Error_Msg_N ("cannot give record rep clause for subtype", N);
1763          return;
1764
1765       elsif Has_Record_Rep_Clause (Rectype) then
1766          Error_Msg_N ("duplicate record rep clause ignored", N);
1767          return;
1768
1769       elsif Rep_Item_Too_Late (Rectype, N) then
1770          return;
1771       end if;
1772
1773       if Present (Mod_Clause (N)) then
1774          declare
1775             Loc     : constant Source_Ptr := Sloc (N);
1776             M       : constant Node_Id := Mod_Clause (N);
1777             P       : constant List_Id := Pragmas_Before (M);
1778             AtM_Nod : Node_Id;
1779
1780             Mod_Val : Uint;
1781             pragma Warnings (Off, Mod_Val);
1782
1783          begin
1784             Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
1785
1786             if Warn_On_Obsolescent_Feature then
1787                Error_Msg_N
1788                  ("mod clause is an obsolescent feature ('R'M 'J.8)?", N);
1789                Error_Msg_N
1790                  ("\use alignment attribute definition clause instead?", N);
1791             end if;
1792
1793             if Present (P) then
1794                Analyze_List (P);
1795             end if;
1796
1797             --  In ASIS_Mode mode, expansion is disabled, but we must
1798             --  convert the Mod clause into an alignment clause anyway, so
1799             --  that the back-end can compute and back-annotate properly the
1800             --  size and alignment of types that may include this record.
1801
1802             if Operating_Mode = Check_Semantics
1803               and then ASIS_Mode
1804             then
1805                AtM_Nod :=
1806                  Make_Attribute_Definition_Clause (Loc,
1807                    Name       => New_Reference_To (Base_Type (Rectype), Loc),
1808                    Chars      => Name_Alignment,
1809                    Expression => Relocate_Node (Expression (M)));
1810
1811                Set_From_At_Mod (AtM_Nod);
1812                Insert_After (N, AtM_Nod);
1813                Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
1814                Set_Mod_Clause (N, Empty);
1815
1816             else
1817                --  Get the alignment value to perform error checking
1818
1819                Mod_Val := Get_Alignment_Value (Expression (M));
1820
1821             end if;
1822          end;
1823       end if;
1824
1825       --  Clear any existing component clauses for the type (this happens
1826       --  with derived types, where we are now overriding the original)
1827
1828       Fent := First_Entity (Rectype);
1829
1830       Comp := Fent;
1831       while Present (Comp) loop
1832          if Ekind (Comp) = E_Component
1833            or else Ekind (Comp) = E_Discriminant
1834          then
1835             Set_Component_Clause (Comp, Empty);
1836          end if;
1837
1838          Next_Entity (Comp);
1839       end loop;
1840
1841       --  All done if no component clauses
1842
1843       CC := First (Component_Clauses (N));
1844
1845       if No (CC) then
1846          return;
1847       end if;
1848
1849       --  If a tag is present, then create a component clause that places
1850       --  it at the start of the record (otherwise gigi may place it after
1851       --  other fields that have rep clauses).
1852
1853       if Nkind (Fent) = N_Defining_Identifier
1854         and then Chars (Fent) = Name_uTag
1855       then
1856          Set_Component_Bit_Offset    (Fent, Uint_0);
1857          Set_Normalized_Position     (Fent, Uint_0);
1858          Set_Normalized_First_Bit    (Fent, Uint_0);
1859          Set_Normalized_Position_Max (Fent, Uint_0);
1860          Init_Esize                  (Fent, System_Address_Size);
1861
1862          Set_Component_Clause    (Fent,
1863            Make_Component_Clause (Loc,
1864              Component_Name =>
1865                Make_Identifier (Loc,
1866                  Chars => Name_uTag),
1867
1868              Position  =>
1869                Make_Integer_Literal (Loc,
1870                  Intval => Uint_0),
1871
1872              First_Bit =>
1873                Make_Integer_Literal (Loc,
1874                  Intval => Uint_0),
1875
1876              Last_Bit  =>
1877                Make_Integer_Literal (Loc,
1878                  UI_From_Int (System_Address_Size))));
1879
1880          Ccount := Ccount + 1;
1881       end if;
1882
1883       --  A representation like this applies to the base type
1884
1885       Set_Has_Record_Rep_Clause (Base_Type (Rectype));
1886       Set_Has_Non_Standard_Rep  (Base_Type (Rectype));
1887       Set_Has_Specified_Layout  (Base_Type (Rectype));
1888
1889       Max_Bit_So_Far := Uint_Minus_1;
1890       Overlap_Check_Required := False;
1891
1892       --  Process the component clauses
1893
1894       while Present (CC) loop
1895
1896          --  If pragma, just analyze it
1897
1898          if Nkind (CC) = N_Pragma then
1899             Analyze (CC);
1900
1901          --  Processing for real component clause
1902
1903          else
1904             Ccount := Ccount + 1;
1905             Posit := Static_Integer (Position  (CC));
1906             Fbit  := Static_Integer (First_Bit (CC));
1907             Lbit  := Static_Integer (Last_Bit  (CC));
1908
1909             if Posit /= No_Uint
1910               and then Fbit /= No_Uint
1911               and then Lbit /= No_Uint
1912             then
1913                if Posit < 0 then
1914                   Error_Msg_N
1915                     ("position cannot be negative", Position (CC));
1916
1917                elsif Fbit < 0 then
1918                   Error_Msg_N
1919                     ("first bit cannot be negative", First_Bit (CC));
1920
1921                --  Values look OK, so find the corresponding record component
1922                --  Even though the syntax allows an attribute reference for
1923                --  implementation-defined components, GNAT does not allow the
1924                --  tag to get an explicit position.
1925
1926                elsif Nkind (Component_Name (CC)) = N_Attribute_Reference then
1927                   if Attribute_Name (Component_Name (CC)) = Name_Tag then
1928                      Error_Msg_N ("position of tag cannot be specified", CC);
1929                   else
1930                      Error_Msg_N ("illegal component name", CC);
1931                   end if;
1932
1933                else
1934                   Comp := First_Entity (Rectype);
1935                   while Present (Comp) loop
1936                      exit when Chars (Comp) = Chars (Component_Name (CC));
1937                      Next_Entity (Comp);
1938                   end loop;
1939
1940                   if No (Comp) then
1941
1942                      --  Maybe component of base type that is absent from
1943                      --  statically constrained first subtype.
1944
1945                      Comp := First_Entity (Base_Type (Rectype));
1946                      while Present (Comp) loop
1947                         exit when Chars (Comp) = Chars (Component_Name (CC));
1948                         Next_Entity (Comp);
1949                      end loop;
1950                   end if;
1951
1952                   if No (Comp) then
1953                      Error_Msg_N
1954                        ("component clause is for non-existent field", CC);
1955
1956                   elsif Present (Component_Clause (Comp)) then
1957                      Error_Msg_Sloc := Sloc (Component_Clause (Comp));
1958                      Error_Msg_N
1959                        ("component clause previously given#", CC);
1960
1961                   else
1962                      --  Update Fbit and Lbit to the actual bit number
1963
1964                      Fbit := Fbit + UI_From_Int (SSU) * Posit;
1965                      Lbit := Lbit + UI_From_Int (SSU) * Posit;
1966
1967                      if Fbit <= Max_Bit_So_Far then
1968                         Overlap_Check_Required := True;
1969                      else
1970                         Max_Bit_So_Far := Lbit;
1971                      end if;
1972
1973                      if Has_Size_Clause (Rectype)
1974                        and then Esize (Rectype) <= Lbit
1975                      then
1976                         Error_Msg_N
1977                           ("bit number out of range of specified size",
1978                            Last_Bit (CC));
1979                      else
1980                         Set_Component_Clause     (Comp, CC);
1981                         Set_Component_Bit_Offset (Comp, Fbit);
1982                         Set_Esize                (Comp, 1 + (Lbit - Fbit));
1983                         Set_Normalized_First_Bit (Comp, Fbit mod SSU);
1984                         Set_Normalized_Position  (Comp, Fbit / SSU);
1985
1986                         Set_Normalized_Position_Max
1987                           (Fent, Normalized_Position (Fent));
1988
1989                         if Is_Tagged_Type (Rectype)
1990                           and then Fbit < System_Address_Size
1991                         then
1992                            Error_Msg_NE
1993                              ("component overlaps tag field of&",
1994                               CC, Rectype);
1995                         end if;
1996
1997                         --  This information is also set in the corresponding
1998                         --  component of the base type, found by accessing the
1999                         --  Original_Record_Component link if it is present.
2000
2001                         Ocomp := Original_Record_Component (Comp);
2002
2003                         if Hbit < Lbit then
2004                            Hbit := Lbit;
2005                         end if;
2006
2007                         Check_Size
2008                           (Component_Name (CC),
2009                            Etype (Comp),
2010                            Esize (Comp),
2011                            Biased);
2012
2013                         Set_Has_Biased_Representation (Comp, Biased);
2014
2015                         if Present (Ocomp) then
2016                            Set_Component_Clause     (Ocomp, CC);
2017                            Set_Component_Bit_Offset (Ocomp, Fbit);
2018                            Set_Normalized_First_Bit (Ocomp, Fbit mod SSU);
2019                            Set_Normalized_Position  (Ocomp, Fbit / SSU);
2020                            Set_Esize                (Ocomp, 1 + (Lbit - Fbit));
2021
2022                            Set_Normalized_Position_Max
2023                              (Ocomp, Normalized_Position (Ocomp));
2024
2025                            Set_Has_Biased_Representation
2026                              (Ocomp, Has_Biased_Representation (Comp));
2027                         end if;
2028
2029                         if Esize (Comp) < 0 then
2030                            Error_Msg_N ("component size is negative", CC);
2031                         end if;
2032                      end if;
2033                   end if;
2034                end if;
2035             end if;
2036          end if;
2037
2038          Next (CC);
2039       end loop;
2040
2041       --  Now that we have processed all the component clauses, check for
2042       --  overlap. We have to leave this till last, since the components
2043       --  can appear in any arbitrary order in the representation clause.
2044
2045       --  We do not need this check if all specified ranges were monotonic,
2046       --  as recorded by Overlap_Check_Required being False at this stage.
2047
2048       --  This first section checks if there are any overlapping entries
2049       --  at all. It does this by sorting all entries and then seeing if
2050       --  there are any overlaps. If there are none, then that is decisive,
2051       --  but if there are overlaps, they may still be OK (they may result
2052       --  from fields in different variants).
2053
2054       if Overlap_Check_Required then
2055          Overlap_Check1 : declare
2056
2057             OC_Fbit : array (0 .. Ccount) of Uint;
2058             --  First-bit values for component clauses, the value is the
2059             --  offset of the first bit of the field from start of record.
2060             --  The zero entry is for use in sorting.
2061
2062             OC_Lbit : array (0 .. Ccount) of Uint;
2063             --  Last-bit values for component clauses, the value is the
2064             --  offset of the last bit of the field from start of record.
2065             --  The zero entry is for use in sorting.
2066
2067             OC_Count : Natural := 0;
2068             --  Count of entries in OC_Fbit and OC_Lbit
2069
2070             function OC_Lt (Op1, Op2 : Natural) return Boolean;
2071             --  Compare routine for Sort (See GNAT.Heap_Sort_A)
2072
2073             procedure OC_Move (From : Natural; To : Natural);
2074             --  Move routine for Sort (see GNAT.Heap_Sort_A)
2075
2076             function OC_Lt (Op1, Op2 : Natural) return Boolean is
2077             begin
2078                return OC_Fbit (Op1) < OC_Fbit (Op2);
2079             end OC_Lt;
2080
2081             procedure OC_Move (From : Natural; To : Natural) is
2082             begin
2083                OC_Fbit (To) := OC_Fbit (From);
2084                OC_Lbit (To) := OC_Lbit (From);
2085             end OC_Move;
2086
2087          begin
2088             CC := First (Component_Clauses (N));
2089             while Present (CC) loop
2090                if Nkind (CC) /= N_Pragma then
2091                   Posit := Static_Integer (Position  (CC));
2092                   Fbit  := Static_Integer (First_Bit (CC));
2093                   Lbit  := Static_Integer (Last_Bit  (CC));
2094
2095                   if Posit /= No_Uint
2096                     and then Fbit /= No_Uint
2097                     and then Lbit /= No_Uint
2098                   then
2099                      OC_Count := OC_Count + 1;
2100                      Posit := Posit * SSU;
2101                      OC_Fbit (OC_Count) := Fbit + Posit;
2102                      OC_Lbit (OC_Count) := Lbit + Posit;
2103                   end if;
2104                end if;
2105
2106                Next (CC);
2107             end loop;
2108
2109             Sort
2110               (OC_Count,
2111                OC_Move'Unrestricted_Access,
2112                OC_Lt'Unrestricted_Access);
2113
2114             Overlap_Check_Required := False;
2115             for J in 1 .. OC_Count - 1 loop
2116                if OC_Lbit (J) >= OC_Fbit (J + 1) then
2117                   Overlap_Check_Required := True;
2118                   exit;
2119                end if;
2120             end loop;
2121          end Overlap_Check1;
2122       end if;
2123
2124       --  If Overlap_Check_Required is still True, then we have to do
2125       --  the full scale overlap check, since we have at least two fields
2126       --  that do overlap, and we need to know if that is OK since they
2127       --  are in the same variant, or whether we have a definite problem
2128
2129       if Overlap_Check_Required then
2130          Overlap_Check2 : declare
2131             C1_Ent, C2_Ent : Entity_Id;
2132             --  Entities of components being checked for overlap
2133
2134             Clist : Node_Id;
2135             --  Component_List node whose Component_Items are being checked
2136
2137             Citem : Node_Id;
2138             --  Component declaration for component being checked
2139
2140          begin
2141             C1_Ent := First_Entity (Base_Type (Rectype));
2142
2143             --  Loop through all components in record. For each component check
2144             --  for overlap with any of the preceding elements on the component
2145             --  list containing the component, and also, if the component is in
2146             --  a variant, check against components outside the case structure.
2147             --  This latter test is repeated recursively up the variant tree.
2148
2149             Main_Component_Loop : while Present (C1_Ent) loop
2150                if Ekind (C1_Ent) /= E_Component
2151                  and then Ekind (C1_Ent) /= E_Discriminant
2152                then
2153                   goto Continue_Main_Component_Loop;
2154                end if;
2155
2156                --  Skip overlap check if entity has no declaration node. This
2157                --  happens with discriminants in constrained derived types.
2158                --  Probably we are missing some checks as a result, but that
2159                --  does not seem terribly serious ???
2160
2161                if No (Declaration_Node (C1_Ent)) then
2162                   goto Continue_Main_Component_Loop;
2163                end if;
2164
2165                Clist := Parent (List_Containing (Declaration_Node (C1_Ent)));
2166
2167                --  Loop through component lists that need checking. Check the
2168                --  current component list and all lists in variants above us.
2169
2170                Component_List_Loop : loop
2171
2172                   --  If derived type definition, go to full declaration
2173                   --  If at outer level, check discriminants if there are any
2174
2175                   if Nkind (Clist) = N_Derived_Type_Definition then
2176                      Clist := Parent (Clist);
2177                   end if;
2178
2179                   --  Outer level of record definition, check discriminants
2180
2181                   if Nkind (Clist) = N_Full_Type_Declaration
2182                     or else Nkind (Clist) = N_Private_Type_Declaration
2183                   then
2184                      if Has_Discriminants (Defining_Identifier (Clist)) then
2185                         C2_Ent :=
2186                           First_Discriminant (Defining_Identifier (Clist));
2187
2188                         while Present (C2_Ent) loop
2189                            exit when C1_Ent = C2_Ent;
2190                            Check_Component_Overlap (C1_Ent, C2_Ent);
2191                            Next_Discriminant (C2_Ent);
2192                         end loop;
2193                      end if;
2194
2195                   --  Record extension case
2196
2197                   elsif Nkind (Clist) = N_Derived_Type_Definition then
2198                      Clist := Empty;
2199
2200                   --  Otherwise check one component list
2201
2202                   else
2203                      Citem := First (Component_Items (Clist));
2204
2205                      while Present (Citem) loop
2206                         if Nkind (Citem) = N_Component_Declaration then
2207                            C2_Ent := Defining_Identifier (Citem);
2208                            exit when C1_Ent = C2_Ent;
2209                            Check_Component_Overlap (C1_Ent, C2_Ent);
2210                         end if;
2211
2212                         Next (Citem);
2213                      end loop;
2214                   end if;
2215
2216                   --  Check for variants above us (the parent of the Clist can
2217                   --  be a variant, in which case its parent is a variant part,
2218                   --  and the parent of the variant part is a component list
2219                   --  whose components must all be checked against the current
2220                   --  component for overlap.
2221
2222                   if Nkind (Parent (Clist)) = N_Variant then
2223                      Clist := Parent (Parent (Parent (Clist)));
2224
2225                   --  Check for possible discriminant part in record, this is
2226                   --  treated essentially as another level in the recursion.
2227                   --  For this case we have the parent of the component list
2228                   --  is the record definition, and its parent is the full
2229                   --  type declaration which contains the discriminant
2230                   --  specifications.
2231
2232                   elsif Nkind (Parent (Clist)) = N_Record_Definition then
2233                      Clist := Parent (Parent ((Clist)));
2234
2235                   --  If neither of these two cases, we are at the top of
2236                   --  the tree
2237
2238                   else
2239                      exit Component_List_Loop;
2240                   end if;
2241                end loop Component_List_Loop;
2242
2243                <<Continue_Main_Component_Loop>>
2244                   Next_Entity (C1_Ent);
2245
2246             end loop Main_Component_Loop;
2247          end Overlap_Check2;
2248       end if;
2249
2250       --  For records that have component clauses for all components, and
2251       --  whose size is less than or equal to 32, we need to know the size
2252       --  in the front end to activate possible packed array processing
2253       --  where the component type is a record.
2254
2255       --  At this stage Hbit + 1 represents the first unused bit from all
2256       --  the component clauses processed, so if the component clauses are
2257       --  complete, then this is the length of the record.
2258
2259       --  For records longer than System.Storage_Unit, and for those where
2260       --  not all components have component clauses, the back end determines
2261       --  the length (it may for example be appopriate to round up the size
2262       --  to some convenient boundary, based on alignment considerations etc).
2263
2264       if Unknown_RM_Size (Rectype)
2265         and then Hbit + 1 <= 32
2266       then
2267          --  Nothing to do if at least one component with no component clause
2268
2269          Comp := First_Entity (Rectype);
2270          while Present (Comp) loop
2271             if Ekind (Comp) = E_Component
2272               or else Ekind (Comp) = E_Discriminant
2273             then
2274                if No (Component_Clause (Comp)) then
2275                   return;
2276                end if;
2277             end if;
2278
2279             Next_Entity (Comp);
2280          end loop;
2281
2282          --  If we fall out of loop, all components have component clauses
2283          --  and so we can set the size to the maximum value.
2284
2285          Set_RM_Size (Rectype, Hbit + 1);
2286       end if;
2287    end Analyze_Record_Representation_Clause;
2288
2289    -----------------------------
2290    -- Check_Component_Overlap --
2291    -----------------------------
2292
2293    procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id) is
2294    begin
2295       if Present (Component_Clause (C1_Ent))
2296         and then Present (Component_Clause (C2_Ent))
2297       then
2298          --  Exclude odd case where we have two tag fields in the same
2299          --  record, both at location zero. This seems a bit strange,
2300          --  but it seems to happen in some circumstances ???
2301
2302          if Chars (C1_Ent) = Name_uTag
2303            and then Chars (C2_Ent) = Name_uTag
2304          then
2305             return;
2306          end if;
2307
2308          --  Here we check if the two fields overlap
2309
2310          declare
2311             S1 : constant Uint := Component_Bit_Offset (C1_Ent);
2312             S2 : constant Uint := Component_Bit_Offset (C2_Ent);
2313             E1 : constant Uint := S1 + Esize (C1_Ent);
2314             E2 : constant Uint := S2 + Esize (C2_Ent);
2315
2316          begin
2317             if E2 <= S1 or else E1 <= S2 then
2318                null;
2319             else
2320                Error_Msg_Node_2 :=
2321                  Component_Name (Component_Clause (C2_Ent));
2322                Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
2323                Error_Msg_Node_1 :=
2324                  Component_Name (Component_Clause (C1_Ent));
2325                Error_Msg_N
2326                  ("component& overlaps & #",
2327                   Component_Name (Component_Clause (C1_Ent)));
2328             end if;
2329          end;
2330       end if;
2331    end Check_Component_Overlap;
2332
2333    -----------------------------------
2334    -- Check_Constant_Address_Clause --
2335    -----------------------------------
2336
2337    procedure Check_Constant_Address_Clause
2338      (Expr  : Node_Id;
2339       U_Ent : Entity_Id)
2340    is
2341       procedure Check_At_Constant_Address (Nod : Node_Id);
2342       --  Checks that the given node N represents a name whose 'Address
2343       --  is constant (in the same sense as OK_Constant_Address_Clause,
2344       --  i.e. the address value is the same at the point of declaration
2345       --  of U_Ent and at the time of elaboration of the address clause.
2346
2347       procedure Check_Expr_Constants (Nod : Node_Id);
2348       --  Checks that Nod meets the requirements for a constant address
2349       --  clause in the sense of the enclosing procedure.
2350
2351       procedure Check_List_Constants (Lst : List_Id);
2352       --  Check that all elements of list Lst meet the requirements for a
2353       --  constant address clause in the sense of the enclosing procedure.
2354
2355       -------------------------------
2356       -- Check_At_Constant_Address --
2357       -------------------------------
2358
2359       procedure Check_At_Constant_Address (Nod : Node_Id) is
2360       begin
2361          if Is_Entity_Name (Nod) then
2362             if Present (Address_Clause (Entity ((Nod)))) then
2363                Error_Msg_NE
2364                  ("invalid address clause for initialized object &!",
2365                            Nod, U_Ent);
2366                Error_Msg_NE
2367                  ("address for& cannot" &
2368                     " depend on another address clause! ('R'M 13.1(22))!",
2369                   Nod, U_Ent);
2370
2371             elsif In_Same_Source_Unit (Entity (Nod), U_Ent)
2372               and then Sloc (U_Ent) < Sloc (Entity (Nod))
2373             then
2374                Error_Msg_NE
2375                  ("invalid address clause for initialized object &!",
2376                   Nod, U_Ent);
2377                Error_Msg_Name_1 := Chars (Entity (Nod));
2378                Error_Msg_Name_2 := Chars (U_Ent);
2379                Error_Msg_N
2380                  ("\% must be defined before % ('R'M 13.1(22))!",
2381                   Nod);
2382             end if;
2383
2384          elsif Nkind (Nod) = N_Selected_Component then
2385             declare
2386                T : constant Entity_Id := Etype (Prefix (Nod));
2387
2388             begin
2389                if (Is_Record_Type (T)
2390                     and then Has_Discriminants (T))
2391                  or else
2392                   (Is_Access_Type (T)
2393                      and then Is_Record_Type (Designated_Type (T))
2394                      and then Has_Discriminants (Designated_Type (T)))
2395                then
2396                   Error_Msg_NE
2397                     ("invalid address clause for initialized object &!",
2398                      Nod, U_Ent);
2399                   Error_Msg_N
2400                     ("\address cannot depend on component" &
2401                      " of discriminated record ('R'M 13.1(22))!",
2402                      Nod);
2403                else
2404                   Check_At_Constant_Address (Prefix (Nod));
2405                end if;
2406             end;
2407
2408          elsif Nkind (Nod) = N_Indexed_Component then
2409             Check_At_Constant_Address (Prefix (Nod));
2410             Check_List_Constants (Expressions (Nod));
2411
2412          else
2413             Check_Expr_Constants (Nod);
2414          end if;
2415       end Check_At_Constant_Address;
2416
2417       --------------------------
2418       -- Check_Expr_Constants --
2419       --------------------------
2420
2421       procedure Check_Expr_Constants (Nod : Node_Id) is
2422          Loc_U_Ent : constant Source_Ptr := Sloc (U_Ent);
2423          Ent       : Entity_Id           := Empty;
2424
2425       begin
2426          if Nkind (Nod) in N_Has_Etype
2427            and then Etype (Nod) = Any_Type
2428          then
2429             return;
2430          end if;
2431
2432          case Nkind (Nod) is
2433             when N_Empty | N_Error =>
2434                return;
2435
2436             when N_Identifier | N_Expanded_Name =>
2437                Ent := Entity (Nod);
2438
2439                --  We need to look at the original node if it is different
2440                --  from the node, since we may have rewritten things and
2441                --  substituted an identifier representing the rewrite.
2442
2443                if Original_Node (Nod) /= Nod then
2444                   Check_Expr_Constants (Original_Node (Nod));
2445
2446                   --  If the node is an object declaration without initial
2447                   --  value, some code has been expanded, and the expression
2448                   --  is not constant, even if the constituents might be
2449                   --  acceptable, as in  A'Address + offset.
2450
2451                   if Ekind (Ent) = E_Variable
2452                     and then Nkind (Declaration_Node (Ent))
2453                       = N_Object_Declaration
2454                     and then
2455                       No (Expression (Declaration_Node (Ent)))
2456                   then
2457                      Error_Msg_NE
2458                        ("invalid address clause for initialized object &!",
2459                         Nod, U_Ent);
2460
2461                   --  If entity is constant, it may be the result of expanding
2462                   --  a check. We must verify that its declaration appears
2463                   --  before the object in question, else we also reject the
2464                   --  address clause.
2465
2466                   elsif Ekind (Ent) = E_Constant
2467                     and then In_Same_Source_Unit (Ent, U_Ent)
2468                     and then Sloc (Ent) > Loc_U_Ent
2469                   then
2470                      Error_Msg_NE
2471                        ("invalid address clause for initialized object &!",
2472                         Nod, U_Ent);
2473                   end if;
2474
2475                   return;
2476                end if;
2477
2478                --  Otherwise look at the identifier and see if it is OK
2479
2480                if Ekind (Ent) = E_Named_Integer
2481                     or else
2482                   Ekind (Ent) = E_Named_Real
2483                     or else
2484                   Is_Type (Ent)
2485                then
2486                   return;
2487
2488                elsif
2489                   Ekind (Ent) = E_Constant
2490                     or else
2491                   Ekind (Ent) = E_In_Parameter
2492                then
2493                   --  This is the case where we must have Ent defined
2494                   --  before U_Ent. Clearly if they are in different
2495                   --  units this requirement is met since the unit
2496                   --  containing Ent is already processed.
2497
2498                   if not In_Same_Source_Unit (Ent, U_Ent) then
2499                      return;
2500
2501                   --  Otherwise location of Ent must be before the
2502                   --  location of U_Ent, that's what prior defined means.
2503
2504                   elsif Sloc (Ent) < Loc_U_Ent then
2505                      return;
2506
2507                   else
2508                      Error_Msg_NE
2509                        ("invalid address clause for initialized object &!",
2510                         Nod, U_Ent);
2511                      Error_Msg_Name_1 := Chars (Ent);
2512                      Error_Msg_Name_2 := Chars (U_Ent);
2513                      Error_Msg_N
2514                        ("\% must be defined before % ('R'M 13.1(22))!",
2515                         Nod);
2516                   end if;
2517
2518                elsif Nkind (Original_Node (Nod)) = N_Function_Call then
2519                   Check_Expr_Constants (Original_Node (Nod));
2520
2521                else
2522                   Error_Msg_NE
2523                     ("invalid address clause for initialized object &!",
2524                      Nod, U_Ent);
2525
2526                   if Comes_From_Source (Ent) then
2527                      Error_Msg_Name_1 := Chars (Ent);
2528                      Error_Msg_N
2529                        ("\reference to variable% not allowed"
2530                           & " ('R'M 13.1(22))!", Nod);
2531                   else
2532                      Error_Msg_N
2533                        ("non-static expression not allowed"
2534                           & " ('R'M 13.1(22))!", Nod);
2535                   end if;
2536                end if;
2537
2538             when N_Integer_Literal   =>
2539
2540                --  If this is a rewritten unchecked conversion, in a system
2541                --  where Address is an integer type, always use the base type
2542                --  for a literal value. This is user-friendly and prevents
2543                --  order-of-elaboration issues with instances of unchecked
2544                --  conversion.
2545
2546                if Nkind (Original_Node (Nod)) = N_Function_Call then
2547                   Set_Etype (Nod, Base_Type (Etype (Nod)));
2548                end if;
2549
2550             when N_Real_Literal      |
2551                  N_String_Literal    |
2552                  N_Character_Literal =>
2553                return;
2554
2555             when N_Range =>
2556                Check_Expr_Constants (Low_Bound (Nod));
2557                Check_Expr_Constants (High_Bound (Nod));
2558
2559             when N_Explicit_Dereference =>
2560                Check_Expr_Constants (Prefix (Nod));
2561
2562             when N_Indexed_Component =>
2563                Check_Expr_Constants (Prefix (Nod));
2564                Check_List_Constants (Expressions (Nod));
2565
2566             when N_Slice =>
2567                Check_Expr_Constants (Prefix (Nod));
2568                Check_Expr_Constants (Discrete_Range (Nod));
2569
2570             when N_Selected_Component =>
2571                Check_Expr_Constants (Prefix (Nod));
2572
2573             when N_Attribute_Reference =>
2574
2575                if Attribute_Name (Nod) = Name_Address
2576                    or else
2577                   Attribute_Name (Nod) = Name_Access
2578                     or else
2579                   Attribute_Name (Nod) = Name_Unchecked_Access
2580                     or else
2581                   Attribute_Name (Nod) = Name_Unrestricted_Access
2582                then
2583                   Check_At_Constant_Address (Prefix (Nod));
2584
2585                else
2586                   Check_Expr_Constants (Prefix (Nod));
2587                   Check_List_Constants (Expressions (Nod));
2588                end if;
2589
2590             when N_Aggregate =>
2591                Check_List_Constants (Component_Associations (Nod));
2592                Check_List_Constants (Expressions (Nod));
2593
2594             when N_Component_Association =>
2595                Check_Expr_Constants (Expression (Nod));
2596
2597             when N_Extension_Aggregate =>
2598                Check_Expr_Constants (Ancestor_Part (Nod));
2599                Check_List_Constants (Component_Associations (Nod));
2600                Check_List_Constants (Expressions (Nod));
2601
2602             when N_Null =>
2603                return;
2604
2605             when N_Binary_Op | N_And_Then | N_Or_Else | N_In | N_Not_In =>
2606                Check_Expr_Constants (Left_Opnd (Nod));
2607                Check_Expr_Constants (Right_Opnd (Nod));
2608
2609             when N_Unary_Op =>
2610                Check_Expr_Constants (Right_Opnd (Nod));
2611
2612             when N_Type_Conversion           |
2613                  N_Qualified_Expression      |
2614                  N_Allocator                 =>
2615                Check_Expr_Constants (Expression (Nod));
2616
2617             when N_Unchecked_Type_Conversion =>
2618                Check_Expr_Constants (Expression (Nod));
2619
2620                --  If this is a rewritten unchecked conversion, subtypes
2621                --  in this node are those created within the instance.
2622                --  To avoid order of elaboration issues, replace them
2623                --  with their base types. Note that address clauses can
2624                --  cause order of elaboration problems because they are
2625                --  elaborated by the back-end at the point of definition,
2626                --  and may mention entities declared in between (as long
2627                --  as everything is static). It is user-friendly to allow
2628                --  unchecked conversions in this context.
2629
2630                if Nkind (Original_Node (Nod)) = N_Function_Call then
2631                   Set_Etype (Expression (Nod),
2632                     Base_Type (Etype (Expression (Nod))));
2633                   Set_Etype (Nod, Base_Type (Etype (Nod)));
2634                end if;
2635
2636             when N_Function_Call =>
2637                if not Is_Pure (Entity (Name (Nod))) then
2638                   Error_Msg_NE
2639                     ("invalid address clause for initialized object &!",
2640                      Nod, U_Ent);
2641
2642                   Error_Msg_NE
2643                     ("\function & is not pure ('R'M 13.1(22))!",
2644                      Nod, Entity (Name (Nod)));
2645
2646                else
2647                   Check_List_Constants (Parameter_Associations (Nod));
2648                end if;
2649
2650             when N_Parameter_Association =>
2651                Check_Expr_Constants (Explicit_Actual_Parameter (Nod));
2652
2653             when others =>
2654                Error_Msg_NE
2655                  ("invalid address clause for initialized object &!",
2656                   Nod, U_Ent);
2657                Error_Msg_NE
2658                  ("\must be constant defined before& ('R'M 13.1(22))!",
2659                   Nod, U_Ent);
2660          end case;
2661       end Check_Expr_Constants;
2662
2663       --------------------------
2664       -- Check_List_Constants --
2665       --------------------------
2666
2667       procedure Check_List_Constants (Lst : List_Id) is
2668          Nod1 : Node_Id;
2669
2670       begin
2671          if Present (Lst) then
2672             Nod1 := First (Lst);
2673             while Present (Nod1) loop
2674                Check_Expr_Constants (Nod1);
2675                Next (Nod1);
2676             end loop;
2677          end if;
2678       end Check_List_Constants;
2679
2680    --  Start of processing for Check_Constant_Address_Clause
2681
2682    begin
2683       Check_Expr_Constants (Expr);
2684    end Check_Constant_Address_Clause;
2685
2686    ----------------
2687    -- Check_Size --
2688    ----------------
2689
2690    procedure Check_Size
2691      (N      : Node_Id;
2692       T      : Entity_Id;
2693       Siz    : Uint;
2694       Biased : out Boolean)
2695    is
2696       UT : constant Entity_Id := Underlying_Type (T);
2697       M  : Uint;
2698
2699    begin
2700       Biased := False;
2701
2702       --  Dismiss cases for generic types or types with previous errors
2703
2704       if No (UT)
2705         or else UT = Any_Type
2706         or else Is_Generic_Type (UT)
2707         or else Is_Generic_Type (Root_Type (UT))
2708       then
2709          return;
2710
2711       --  Check case of bit packed array
2712
2713       elsif Is_Array_Type (UT)
2714         and then Known_Static_Component_Size (UT)
2715         and then Is_Bit_Packed_Array (UT)
2716       then
2717          declare
2718             Asiz : Uint;
2719             Indx : Node_Id;
2720             Ityp : Entity_Id;
2721
2722          begin
2723             Asiz := Component_Size (UT);
2724             Indx := First_Index (UT);
2725             loop
2726                Ityp := Etype (Indx);
2727
2728                --  If non-static bound, then we are not in the business of
2729                --  trying to check the length, and indeed an error will be
2730                --  issued elsewhere, since sizes of non-static array types
2731                --  cannot be set implicitly or explicitly.
2732
2733                if not Is_Static_Subtype (Ityp) then
2734                   return;
2735                end if;
2736
2737                --  Otherwise accumulate next dimension
2738
2739                Asiz := Asiz * (Expr_Value (Type_High_Bound (Ityp)) -
2740                                Expr_Value (Type_Low_Bound  (Ityp)) +
2741                                Uint_1);
2742
2743                Next_Index (Indx);
2744                exit when No (Indx);
2745             end loop;
2746
2747             if Asiz <= Siz then
2748                return;
2749             else
2750                Error_Msg_Uint_1 := Asiz;
2751                Error_Msg_NE
2752                  ("size for& too small, minimum allowed is ^", N, T);
2753                Set_Esize   (T, Asiz);
2754                Set_RM_Size (T, Asiz);
2755             end if;
2756          end;
2757
2758       --  All other composite types are ignored
2759
2760       elsif Is_Composite_Type (UT) then
2761          return;
2762
2763       --  For fixed-point types, don't check minimum if type is not frozen,
2764       --  since we don't know all the characteristics of the type that can
2765       --  affect the size (e.g. a specified small) till freeze time.
2766
2767       elsif Is_Fixed_Point_Type (UT)
2768         and then not Is_Frozen (UT)
2769       then
2770          null;
2771
2772       --  Cases for which a minimum check is required
2773
2774       else
2775          --  Ignore if specified size is correct for the type
2776
2777          if Known_Esize (UT) and then Siz = Esize (UT) then
2778             return;
2779          end if;
2780
2781          --  Otherwise get minimum size
2782
2783          M := UI_From_Int (Minimum_Size (UT));
2784
2785          if Siz < M then
2786
2787             --  Size is less than minimum size, but one possibility remains
2788             --  that we can manage with the new size if we bias the type
2789
2790             M := UI_From_Int (Minimum_Size (UT, Biased => True));
2791
2792             if Siz < M then
2793                Error_Msg_Uint_1 := M;
2794                Error_Msg_NE
2795                  ("size for& too small, minimum allowed is ^", N, T);
2796                Set_Esize (T, M);
2797                Set_RM_Size (T, M);
2798             else
2799                Biased := True;
2800             end if;
2801          end if;
2802       end if;
2803    end Check_Size;
2804
2805    -------------------------
2806    -- Get_Alignment_Value --
2807    -------------------------
2808
2809    function Get_Alignment_Value (Expr : Node_Id) return Uint is
2810       Align : constant Uint := Static_Integer (Expr);
2811
2812    begin
2813       if Align = No_Uint then
2814          return No_Uint;
2815
2816       elsif Align <= 0 then
2817          Error_Msg_N ("alignment value must be positive", Expr);
2818          return No_Uint;
2819
2820       else
2821          for J in Int range 0 .. 64 loop
2822             declare
2823                M : constant Uint := Uint_2 ** J;
2824
2825             begin
2826                exit when M = Align;
2827
2828                if M > Align then
2829                   Error_Msg_N
2830                     ("alignment value must be power of 2", Expr);
2831                   return No_Uint;
2832                end if;
2833             end;
2834          end loop;
2835
2836          return Align;
2837       end if;
2838    end Get_Alignment_Value;
2839
2840    ----------------
2841    -- Initialize --
2842    ----------------
2843
2844    procedure Initialize is
2845    begin
2846       Unchecked_Conversions.Init;
2847    end Initialize;
2848
2849    -------------------------
2850    -- Is_Operational_Item --
2851    -------------------------
2852
2853    function Is_Operational_Item (N : Node_Id) return Boolean is
2854    begin
2855       if Nkind (N) /= N_Attribute_Definition_Clause then
2856          return False;
2857       else
2858          declare
2859             Id    : constant Attribute_Id := Get_Attribute_Id (Chars (N));
2860
2861          begin
2862             return Id = Attribute_Input
2863               or else Id = Attribute_Output
2864               or else Id = Attribute_Read
2865               or else Id = Attribute_Write
2866               or else Id = Attribute_External_Tag;
2867          end;
2868       end if;
2869    end Is_Operational_Item;
2870
2871    --------------------------------------
2872    -- Mark_Aliased_Address_As_Volatile --
2873    --------------------------------------
2874
2875    procedure Mark_Aliased_Address_As_Volatile (N : Node_Id) is
2876       Ent : constant Entity_Id := Address_Aliased_Entity (N);
2877
2878    begin
2879       if Present (Ent) then
2880          Set_Treat_As_Volatile (Ent);
2881       end if;
2882    end Mark_Aliased_Address_As_Volatile;
2883
2884    ------------------
2885    -- Minimum_Size --
2886    ------------------
2887
2888    function Minimum_Size
2889      (T      : Entity_Id;
2890       Biased : Boolean := False) return Nat
2891    is
2892       Lo     : Uint    := No_Uint;
2893       Hi     : Uint    := No_Uint;
2894       LoR    : Ureal   := No_Ureal;
2895       HiR    : Ureal   := No_Ureal;
2896       LoSet  : Boolean := False;
2897       HiSet  : Boolean := False;
2898       B      : Uint;
2899       S      : Nat;
2900       Ancest : Entity_Id;
2901       R_Typ  : constant Entity_Id := Root_Type (T);
2902
2903    begin
2904       --  If bad type, return 0
2905
2906       if T = Any_Type then
2907          return 0;
2908
2909       --  For generic types, just return zero. There cannot be any legitimate
2910       --  need to know such a size, but this routine may be called with a
2911       --  generic type as part of normal processing.
2912
2913       elsif Is_Generic_Type (R_Typ)
2914         or else R_Typ = Any_Type
2915       then
2916          return 0;
2917
2918          --  Access types. Normally an access type cannot have a size smaller
2919          --  than the size of System.Address. The exception is on VMS, where
2920          --  we have short and long addresses, and it is possible for an access
2921          --  type to have a short address size (and thus be less than the size
2922          --  of System.Address itself). We simply skip the check for VMS, and
2923          --  leave the back end to do the check.
2924
2925       elsif Is_Access_Type (T) then
2926          if OpenVMS_On_Target then
2927             return 0;
2928          else
2929             return System_Address_Size;
2930          end if;
2931
2932       --  Floating-point types
2933
2934       elsif Is_Floating_Point_Type (T) then
2935          return UI_To_Int (Esize (R_Typ));
2936
2937       --  Discrete types
2938
2939       elsif Is_Discrete_Type (T) then
2940
2941          --  The following loop is looking for the nearest compile time
2942          --  known bounds following the ancestor subtype chain. The idea
2943          --  is to find the most restrictive known bounds information.
2944
2945          Ancest := T;
2946          loop
2947             if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
2948                return 0;
2949             end if;
2950
2951             if not LoSet then
2952                if Compile_Time_Known_Value (Type_Low_Bound (Ancest)) then
2953                   Lo := Expr_Rep_Value (Type_Low_Bound (Ancest));
2954                   LoSet := True;
2955                   exit when HiSet;
2956                end if;
2957             end if;
2958
2959             if not HiSet then
2960                if Compile_Time_Known_Value (Type_High_Bound (Ancest)) then
2961                   Hi := Expr_Rep_Value (Type_High_Bound (Ancest));
2962                   HiSet := True;
2963                   exit when LoSet;
2964                end if;
2965             end if;
2966
2967             Ancest := Ancestor_Subtype (Ancest);
2968
2969             if No (Ancest) then
2970                Ancest := Base_Type (T);
2971
2972                if Is_Generic_Type (Ancest) then
2973                   return 0;
2974                end if;
2975             end if;
2976          end loop;
2977
2978       --  Fixed-point types. We can't simply use Expr_Value to get the
2979       --  Corresponding_Integer_Value values of the bounds, since these
2980       --  do not get set till the type is frozen, and this routine can
2981       --  be called before the type is frozen. Similarly the test for
2982       --  bounds being static needs to include the case where we have
2983       --  unanalyzed real literals for the same reason.
2984
2985       elsif Is_Fixed_Point_Type (T) then
2986
2987          --  The following loop is looking for the nearest compile time
2988          --  known bounds following the ancestor subtype chain. The idea
2989          --  is to find the most restrictive known bounds information.
2990
2991          Ancest := T;
2992          loop
2993             if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
2994                return 0;
2995             end if;
2996
2997             if not LoSet then
2998                if Nkind (Type_Low_Bound (Ancest)) = N_Real_Literal
2999                  or else Compile_Time_Known_Value (Type_Low_Bound (Ancest))
3000                then
3001                   LoR := Expr_Value_R (Type_Low_Bound (Ancest));
3002                   LoSet := True;
3003                   exit when HiSet;
3004                end if;
3005             end if;
3006
3007             if not HiSet then
3008                if Nkind (Type_High_Bound (Ancest)) = N_Real_Literal
3009                  or else Compile_Time_Known_Value (Type_High_Bound (Ancest))
3010                then
3011                   HiR := Expr_Value_R (Type_High_Bound (Ancest));
3012                   HiSet := True;
3013                   exit when LoSet;
3014                end if;
3015             end if;
3016
3017             Ancest := Ancestor_Subtype (Ancest);
3018
3019             if No (Ancest) then
3020                Ancest := Base_Type (T);
3021
3022                if Is_Generic_Type (Ancest) then
3023                   return 0;
3024                end if;
3025             end if;
3026          end loop;
3027
3028          Lo := UR_To_Uint (LoR / Small_Value (T));
3029          Hi := UR_To_Uint (HiR / Small_Value (T));
3030
3031       --  No other types allowed
3032
3033       else
3034          raise Program_Error;
3035       end if;
3036
3037       --  Fall through with Hi and Lo set. Deal with biased case
3038
3039       if (Biased and then not Is_Fixed_Point_Type (T))
3040         or else Has_Biased_Representation (T)
3041       then
3042          Hi := Hi - Lo;
3043          Lo := Uint_0;
3044       end if;
3045
3046       --  Signed case. Note that we consider types like range 1 .. -1 to be
3047       --  signed for the purpose of computing the size, since the bounds
3048       --  have to be accomodated in the base type.
3049
3050       if Lo < 0 or else Hi < 0 then
3051          S := 1;
3052          B := Uint_1;
3053
3054          --  S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
3055          --  Note that we accommodate the case where the bounds cross. This
3056          --  can happen either because of the way the bounds are declared
3057          --  or because of the algorithm in Freeze_Fixed_Point_Type.
3058
3059          while Lo < -B
3060            or else Hi < -B
3061            or else Lo >= B
3062            or else Hi >= B
3063          loop
3064             B := Uint_2 ** S;
3065             S := S + 1;
3066          end loop;
3067
3068       --  Unsigned case
3069
3070       else
3071          --  If both bounds are positive, make sure that both are represen-
3072          --  table in the case where the bounds are crossed. This can happen
3073          --  either because of the way the bounds are declared, or because of
3074          --  the algorithm in Freeze_Fixed_Point_Type.
3075
3076          if Lo > Hi then
3077             Hi := Lo;
3078          end if;
3079
3080          --  S = size, (can accommodate 0 .. (2**size - 1))
3081
3082          S := 0;
3083          while Hi >= Uint_2 ** S loop
3084             S := S + 1;
3085          end loop;
3086       end if;
3087
3088       return S;
3089    end Minimum_Size;
3090
3091    -------------------------
3092    -- New_Stream_Function --
3093    -------------------------
3094
3095    procedure New_Stream_Function
3096      (N    : Node_Id;
3097       Ent  : Entity_Id;
3098       Subp : Entity_Id;
3099       Nam  : TSS_Name_Type)
3100    is
3101       Loc       : constant Source_Ptr := Sloc (N);
3102       Sname     : constant Name_Id    := Make_TSS_Name (Base_Type (Ent), Nam);
3103       Subp_Id   : Entity_Id;
3104       Subp_Decl : Node_Id;
3105       F         : Entity_Id;
3106       Etyp      : Entity_Id;
3107
3108       function Build_Spec return Node_Id;
3109       --  Used for declaration and renaming declaration, so that this is
3110       --  treated as a renaming_as_body.
3111
3112       ----------------
3113       -- Build_Spec --
3114       ----------------
3115
3116       function Build_Spec return Node_Id is
3117       begin
3118          Subp_Id := Make_Defining_Identifier (Loc, Sname);
3119
3120          return
3121            Make_Function_Specification (Loc,
3122              Defining_Unit_Name => Subp_Id,
3123              Parameter_Specifications =>
3124                New_List (
3125                  Make_Parameter_Specification (Loc,
3126                    Defining_Identifier =>
3127                      Make_Defining_Identifier (Loc, Name_S),
3128                    Parameter_Type =>
3129                      Make_Access_Definition (Loc,
3130                        Subtype_Mark =>
3131                          New_Reference_To (
3132                            Designated_Type (Etype (F)), Loc)))),
3133
3134              Result_Definition =>
3135                New_Reference_To (Etyp, Loc));
3136       end Build_Spec;
3137
3138    --  Start of processing for New_Stream_Function
3139
3140    begin
3141       F    := First_Formal (Subp);
3142       Etyp := Etype (Subp);
3143
3144       if not Is_Tagged_Type (Ent) then
3145          Subp_Decl :=
3146            Make_Subprogram_Declaration (Loc,
3147              Specification => Build_Spec);
3148          Insert_Action (N, Subp_Decl);
3149       end if;
3150
3151       Subp_Decl :=
3152         Make_Subprogram_Renaming_Declaration (Loc,
3153           Specification => Build_Spec,
3154           Name => New_Reference_To (Subp, Loc));
3155
3156       if Is_Tagged_Type (Ent) then
3157          Set_TSS (Base_Type (Ent), Subp_Id);
3158       else
3159          Insert_Action (N, Subp_Decl);
3160          Copy_TSS (Subp_Id, Base_Type (Ent));
3161       end if;
3162    end New_Stream_Function;
3163
3164    --------------------------
3165    -- New_Stream_Procedure --
3166    --------------------------
3167
3168    procedure New_Stream_Procedure
3169      (N     : Node_Id;
3170       Ent   : Entity_Id;
3171       Subp  : Entity_Id;
3172       Nam   : TSS_Name_Type;
3173       Out_P : Boolean := False)
3174    is
3175       Loc       : constant Source_Ptr := Sloc (N);
3176       Sname     : constant Name_Id    := Make_TSS_Name (Base_Type (Ent), Nam);
3177       Subp_Id   : Entity_Id;
3178       Subp_Decl : Node_Id;
3179       F         : Entity_Id;
3180       Etyp      : Entity_Id;
3181
3182       function Build_Spec return Node_Id;
3183       --  Used for declaration and renaming declaration, so that this is
3184       --  treated as a renaming_as_body.
3185
3186       ----------------
3187       -- Build_Spec --
3188       ----------------
3189
3190       function Build_Spec return Node_Id is
3191       begin
3192          Subp_Id := Make_Defining_Identifier (Loc, Sname);
3193
3194          return
3195            Make_Procedure_Specification (Loc,
3196              Defining_Unit_Name => Subp_Id,
3197              Parameter_Specifications =>
3198                New_List (
3199                  Make_Parameter_Specification (Loc,
3200                    Defining_Identifier =>
3201                      Make_Defining_Identifier (Loc, Name_S),
3202                    Parameter_Type =>
3203                      Make_Access_Definition (Loc,
3204                        Subtype_Mark =>
3205                          New_Reference_To (
3206                            Designated_Type (Etype (F)), Loc))),
3207
3208                  Make_Parameter_Specification (Loc,
3209                    Defining_Identifier =>
3210                      Make_Defining_Identifier (Loc, Name_V),
3211                    Out_Present => Out_P,
3212                    Parameter_Type =>
3213                      New_Reference_To (Etyp, Loc))));
3214       end Build_Spec;
3215
3216       --  Start of processing for New_Stream_Procedure
3217
3218    begin
3219       F        := First_Formal (Subp);
3220       Etyp     := Etype (Next_Formal (F));
3221
3222       if not Is_Tagged_Type (Ent) then
3223          Subp_Decl :=
3224            Make_Subprogram_Declaration (Loc,
3225              Specification => Build_Spec);
3226          Insert_Action (N, Subp_Decl);
3227       end if;
3228
3229       Subp_Decl :=
3230         Make_Subprogram_Renaming_Declaration (Loc,
3231           Specification => Build_Spec,
3232           Name => New_Reference_To (Subp, Loc));
3233
3234       if Is_Tagged_Type (Ent) then
3235          Set_TSS (Base_Type (Ent), Subp_Id);
3236       else
3237          Insert_Action (N, Subp_Decl);
3238          Copy_TSS (Subp_Id, Base_Type (Ent));
3239       end if;
3240    end New_Stream_Procedure;
3241
3242    ------------------------
3243    -- Rep_Item_Too_Early --
3244    ------------------------
3245
3246    function Rep_Item_Too_Early (T : Entity_Id; N : Node_Id) return Boolean is
3247    begin
3248       --  Cannot apply rep items that are not operational items
3249       --  to generic types
3250
3251       if Is_Operational_Item (N) then
3252          return False;
3253
3254       elsif Is_Type (T)
3255         and then Is_Generic_Type (Root_Type (T))
3256       then
3257          Error_Msg_N
3258            ("representation item not allowed for generic type", N);
3259          return True;
3260       end if;
3261
3262       --  Otherwise check for incompleted type
3263
3264       if Is_Incomplete_Or_Private_Type (T)
3265         and then No (Underlying_Type (T))
3266       then
3267          Error_Msg_N
3268            ("representation item must be after full type declaration", N);
3269          return True;
3270
3271       --  If the type has incompleted components, a representation clause is
3272       --  illegal but stream attributes and Convention pragmas are correct.
3273
3274       elsif Has_Private_Component (T) then
3275          if Nkind (N) = N_Pragma then
3276             return False;
3277          else
3278             Error_Msg_N
3279               ("representation item must appear after type is fully defined",
3280                 N);
3281             return True;
3282          end if;
3283       else
3284          return False;
3285       end if;
3286    end Rep_Item_Too_Early;
3287
3288    -----------------------
3289    -- Rep_Item_Too_Late --
3290    -----------------------
3291
3292    function Rep_Item_Too_Late
3293      (T     : Entity_Id;
3294       N     : Node_Id;
3295       FOnly : Boolean := False) return Boolean
3296    is
3297       S           : Entity_Id;
3298       Parent_Type : Entity_Id;
3299
3300       procedure Too_Late;
3301       --  Output the too late message. Note that this is not considered a
3302       --  serious error, since the effect is simply that we ignore the
3303       --  representation clause in this case.
3304
3305       --------------
3306       -- Too_Late --
3307       --------------
3308
3309       procedure Too_Late is
3310       begin
3311          Error_Msg_N ("|representation item appears too late!", N);
3312       end Too_Late;
3313
3314    --  Start of processing for Rep_Item_Too_Late
3315
3316    begin
3317       --  First make sure entity is not frozen (RM 13.1(9)). Exclude imported
3318       --  types, which may be frozen if they appear in a representation clause
3319       --  for a local type.
3320
3321       if Is_Frozen (T)
3322         and then not From_With_Type (T)
3323       then
3324          Too_Late;
3325          S := First_Subtype (T);
3326
3327          if Present (Freeze_Node (S)) then
3328             Error_Msg_NE
3329               ("?no more representation items for }!", Freeze_Node (S), S);
3330          end if;
3331
3332          return True;
3333
3334       --  Check for case of non-tagged derived type whose parent either has
3335       --  primitive operations, or is a by reference type (RM 13.1(10)).
3336
3337       elsif Is_Type (T)
3338         and then not FOnly
3339         and then Is_Derived_Type (T)
3340         and then not Is_Tagged_Type (T)
3341       then
3342          Parent_Type := Etype (Base_Type (T));
3343
3344          if Has_Primitive_Operations (Parent_Type) then
3345             Too_Late;
3346             Error_Msg_NE
3347               ("primitive operations already defined for&!", N, Parent_Type);
3348             return True;
3349
3350          elsif Is_By_Reference_Type (Parent_Type) then
3351             Too_Late;
3352             Error_Msg_NE
3353               ("parent type & is a by reference type!", N, Parent_Type);
3354             return True;
3355          end if;
3356       end if;
3357
3358       --  No error, link item into head of chain of rep items for the entity
3359
3360       Record_Rep_Item (T, N);
3361       return False;
3362    end Rep_Item_Too_Late;
3363
3364    -------------------------
3365    -- Same_Representation --
3366    -------------------------
3367
3368    function Same_Representation (Typ1, Typ2 : Entity_Id) return Boolean is
3369       T1 : constant Entity_Id := Underlying_Type (Typ1);
3370       T2 : constant Entity_Id := Underlying_Type (Typ2);
3371
3372    begin
3373       --  A quick check, if base types are the same, then we definitely have
3374       --  the same representation, because the subtype specific representation
3375       --  attributes (Size and Alignment) do not affect representation from
3376       --  the point of view of this test.
3377
3378       if Base_Type (T1) = Base_Type (T2) then
3379          return True;
3380
3381       elsif Is_Private_Type (Base_Type (T2))
3382         and then Base_Type (T1) = Full_View (Base_Type (T2))
3383       then
3384          return True;
3385       end if;
3386
3387       --  Tagged types never have differing representations
3388
3389       if Is_Tagged_Type (T1) then
3390          return True;
3391       end if;
3392
3393       --  Representations are definitely different if conventions differ
3394
3395       if Convention (T1) /= Convention (T2) then
3396          return False;
3397       end if;
3398
3399       --  Representations are different if component alignments differ
3400
3401       if (Is_Record_Type (T1) or else Is_Array_Type (T1))
3402         and then
3403          (Is_Record_Type (T2) or else Is_Array_Type (T2))
3404         and then Component_Alignment (T1) /= Component_Alignment (T2)
3405       then
3406          return False;
3407       end if;
3408
3409       --  For arrays, the only real issue is component size. If we know the
3410       --  component size for both arrays, and it is the same, then that's
3411       --  good enough to know we don't have a change of representation.
3412
3413       if Is_Array_Type (T1) then
3414          if Known_Component_Size (T1)
3415            and then Known_Component_Size (T2)
3416            and then Component_Size (T1) = Component_Size (T2)
3417          then
3418             return True;
3419          end if;
3420       end if;
3421
3422       --  Types definitely have same representation if neither has non-standard
3423       --  representation since default representations are always consistent.
3424       --  If only one has non-standard representation, and the other does not,
3425       --  then we consider that they do not have the same representation. They
3426       --  might, but there is no way of telling early enough.
3427
3428       if Has_Non_Standard_Rep (T1) then
3429          if not Has_Non_Standard_Rep (T2) then
3430             return False;
3431          end if;
3432       else
3433          return not Has_Non_Standard_Rep (T2);
3434       end if;
3435
3436       --  Here the two types both have non-standard representation, and we
3437       --  need to determine if they have the same non-standard representation
3438
3439       --  For arrays, we simply need to test if the component sizes are the
3440       --  same. Pragma Pack is reflected in modified component sizes, so this
3441       --  check also deals with pragma Pack.
3442
3443       if Is_Array_Type (T1) then
3444          return Component_Size (T1) = Component_Size (T2);
3445
3446       --  Tagged types always have the same representation, because it is not
3447       --  possible to specify different representations for common fields.
3448
3449       elsif Is_Tagged_Type (T1) then
3450          return True;
3451
3452       --  Case of record types
3453
3454       elsif Is_Record_Type (T1) then
3455
3456          --  Packed status must conform
3457
3458          if Is_Packed (T1) /= Is_Packed (T2) then
3459             return False;
3460
3461          --  Otherwise we must check components. Typ2 maybe a constrained
3462          --  subtype with fewer components, so we compare the components
3463          --  of the base types.
3464
3465          else
3466             Record_Case : declare
3467                CD1, CD2 : Entity_Id;
3468
3469                function Same_Rep return Boolean;
3470                --  CD1 and CD2 are either components or discriminants. This
3471                --  function tests whether the two have the same representation
3472
3473                --------------
3474                -- Same_Rep --
3475                --------------
3476
3477                function Same_Rep return Boolean is
3478                begin
3479                   if No (Component_Clause (CD1)) then
3480                      return No (Component_Clause (CD2));
3481
3482                   else
3483                      return
3484                         Present (Component_Clause (CD2))
3485                           and then
3486                         Component_Bit_Offset (CD1) = Component_Bit_Offset (CD2)
3487                           and then
3488                         Esize (CD1) = Esize (CD2);
3489                   end if;
3490                end Same_Rep;
3491
3492             --  Start processing for Record_Case
3493
3494             begin
3495                if Has_Discriminants (T1) then
3496                   CD1 := First_Discriminant (T1);
3497                   CD2 := First_Discriminant (T2);
3498
3499                   --  The number of discriminants may be different if the
3500                   --  derived type has fewer (constrained by values). The
3501                   --  invisible discriminants retain the representation of
3502                   --  the original, so the discrepancy does not per se
3503                   --  indicate a different representation.
3504
3505                   while Present (CD1)
3506                     and then Present (CD2)
3507                   loop
3508                      if not Same_Rep then
3509                         return False;
3510                      else
3511                         Next_Discriminant (CD1);
3512                         Next_Discriminant (CD2);
3513                      end if;
3514                   end loop;
3515                end if;
3516
3517                CD1 := First_Component (Underlying_Type (Base_Type (T1)));
3518                CD2 := First_Component (Underlying_Type (Base_Type (T2)));
3519
3520                while Present (CD1) loop
3521                   if not Same_Rep then
3522                      return False;
3523                   else
3524                      Next_Component (CD1);
3525                      Next_Component (CD2);
3526                   end if;
3527                end loop;
3528
3529                return True;
3530             end Record_Case;
3531          end if;
3532
3533       --  For enumeration types, we must check each literal to see if the
3534       --  representation is the same. Note that we do not permit enumeration
3535       --  reprsentation clauses for Character and Wide_Character, so these
3536       --  cases were already dealt with.
3537
3538       elsif Is_Enumeration_Type (T1) then
3539
3540          Enumeration_Case : declare
3541             L1, L2 : Entity_Id;
3542
3543          begin
3544             L1 := First_Literal (T1);
3545             L2 := First_Literal (T2);
3546
3547             while Present (L1) loop
3548                if Enumeration_Rep (L1) /= Enumeration_Rep (L2) then
3549                   return False;
3550                else
3551                   Next_Literal (L1);
3552                   Next_Literal (L2);
3553                end if;
3554             end loop;
3555
3556             return True;
3557
3558          end Enumeration_Case;
3559
3560       --  Any other types have the same representation for these purposes
3561
3562       else
3563          return True;
3564       end if;
3565    end Same_Representation;
3566
3567    --------------------
3568    -- Set_Enum_Esize --
3569    --------------------
3570
3571    procedure Set_Enum_Esize (T : Entity_Id) is
3572       Lo : Uint;
3573       Hi : Uint;
3574       Sz : Nat;
3575
3576    begin
3577       Init_Alignment (T);
3578
3579       --  Find the minimum standard size (8,16,32,64) that fits
3580
3581       Lo := Enumeration_Rep (Entity (Type_Low_Bound (T)));
3582       Hi := Enumeration_Rep (Entity (Type_High_Bound (T)));
3583
3584       if Lo < 0 then
3585          if Lo >= -Uint_2**07 and then Hi < Uint_2**07 then
3586             Sz := Standard_Character_Size;  -- May be > 8 on some targets
3587
3588          elsif Lo >= -Uint_2**15 and then Hi < Uint_2**15 then
3589             Sz := 16;
3590
3591          elsif Lo >= -Uint_2**31 and then Hi < Uint_2**31 then
3592             Sz := 32;
3593
3594          else pragma Assert (Lo >= -Uint_2**63 and then Hi < Uint_2**63);
3595             Sz := 64;
3596          end if;
3597
3598       else
3599          if Hi < Uint_2**08 then
3600             Sz := Standard_Character_Size;  -- May be > 8 on some targets
3601
3602          elsif Hi < Uint_2**16 then
3603             Sz := 16;
3604
3605          elsif Hi < Uint_2**32 then
3606             Sz := 32;
3607
3608          else pragma Assert (Hi < Uint_2**63);
3609             Sz := 64;
3610          end if;
3611       end if;
3612
3613       --  That minimum is the proper size unless we have a foreign convention
3614       --  and the size required is 32 or less, in which case we bump the size
3615       --  up to 32. This is required for C and C++ and seems reasonable for
3616       --  all other foreign conventions.
3617
3618       if Has_Foreign_Convention (T)
3619         and then Esize (T) < Standard_Integer_Size
3620       then
3621          Init_Esize (T, Standard_Integer_Size);
3622
3623       else
3624          Init_Esize (T, Sz);
3625       end if;
3626    end Set_Enum_Esize;
3627
3628    -----------------------------------
3629    -- Validate_Unchecked_Conversion --
3630    -----------------------------------
3631
3632    procedure Validate_Unchecked_Conversion
3633      (N        : Node_Id;
3634       Act_Unit : Entity_Id)
3635    is
3636       Source : Entity_Id;
3637       Target : Entity_Id;
3638       Vnode  : Node_Id;
3639
3640    begin
3641       --  Obtain source and target types. Note that we call Ancestor_Subtype
3642       --  here because the processing for generic instantiation always makes
3643       --  subtypes, and we want the original frozen actual types.
3644
3645       --  If we are dealing with private types, then do the check on their
3646       --  fully declared counterparts if the full declarations have been
3647       --  encountered (they don't have to be visible, but they must exist!)
3648
3649       Source := Ancestor_Subtype (Etype (First_Formal (Act_Unit)));
3650
3651       if Is_Private_Type (Source)
3652         and then Present (Underlying_Type (Source))
3653       then
3654          Source := Underlying_Type (Source);
3655       end if;
3656
3657       Target := Ancestor_Subtype (Etype (Act_Unit));
3658
3659       --  If either type is generic, the instantiation happens within a
3660       --  generic unit, and there is nothing to check. The proper check
3661       --  will happen when the enclosing generic is instantiated.
3662
3663       if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
3664          return;
3665       end if;
3666
3667       if Is_Private_Type (Target)
3668         and then Present (Underlying_Type (Target))
3669       then
3670          Target := Underlying_Type (Target);
3671       end if;
3672
3673       --  Source may be unconstrained array, but not target
3674
3675       if Is_Array_Type (Target)
3676         and then not Is_Constrained (Target)
3677       then
3678          Error_Msg_N
3679            ("unchecked conversion to unconstrained array not allowed", N);
3680          return;
3681       end if;
3682
3683       --  Make entry in unchecked conversion table for later processing
3684       --  by Validate_Unchecked_Conversions, which will check sizes and
3685       --  alignments (using values set by the back-end where possible).
3686       --  This is only done if the appropriate warning is active
3687
3688       if Warn_On_Unchecked_Conversion then
3689          Unchecked_Conversions.Append
3690            (New_Val => UC_Entry'
3691               (Enode  => N,
3692                Source => Source,
3693                Target => Target));
3694
3695          --  If both sizes are known statically now, then back end annotation
3696          --  is not required to do a proper check but if either size is not
3697          --  known statically, then we need the annotation.
3698
3699          if Known_Static_RM_Size (Source)
3700            and then Known_Static_RM_Size (Target)
3701          then
3702             null;
3703          else
3704             Back_Annotate_Rep_Info := True;
3705          end if;
3706       end if;
3707
3708       --  If unchecked conversion to access type, and access type is
3709       --  declared in the same unit as the unchecked conversion, then
3710       --  set the No_Strict_Aliasing flag (no strict aliasing is
3711       --  implicit in this situation).
3712
3713       if Is_Access_Type (Target) and then
3714         In_Same_Source_Unit (Target, N)
3715       then
3716          Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
3717       end if;
3718
3719       --  Generate N_Validate_Unchecked_Conversion node for back end in
3720       --  case the back end needs to perform special validation checks.
3721
3722       --  Shouldn't this be in exp_ch13, since the check only gets done
3723       --  if we have full expansion and the back end is called ???
3724
3725       Vnode :=
3726         Make_Validate_Unchecked_Conversion (Sloc (N));
3727       Set_Source_Type (Vnode, Source);
3728       Set_Target_Type (Vnode, Target);
3729
3730       --  If the unchecked conversion node is in a list, just insert before
3731       --  it. If not we have some strange case, not worth bothering about.
3732
3733       if Is_List_Member (N) then
3734          Insert_After (N, Vnode);
3735       end if;
3736    end Validate_Unchecked_Conversion;
3737
3738    ------------------------------------
3739    -- Validate_Unchecked_Conversions --
3740    ------------------------------------
3741
3742    procedure Validate_Unchecked_Conversions is
3743    begin
3744       for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
3745          declare
3746             T : UC_Entry renames Unchecked_Conversions.Table (N);
3747
3748             Enode  : constant Node_Id   := T.Enode;
3749             Source : constant Entity_Id := T.Source;
3750             Target : constant Entity_Id := T.Target;
3751
3752             Source_Siz    : Uint;
3753             Target_Siz    : Uint;
3754
3755          begin
3756             --  This validation check, which warns if we have unequal sizes
3757             --  for unchecked conversion, and thus potentially implementation
3758             --  dependent semantics, is one of the few occasions on which we
3759             --  use the official RM size instead of Esize. See description
3760             --  in Einfo "Handling of Type'Size Values" for details.
3761
3762             if Serious_Errors_Detected = 0
3763               and then Known_Static_RM_Size (Source)
3764               and then Known_Static_RM_Size (Target)
3765             then
3766                Source_Siz := RM_Size (Source);
3767                Target_Siz := RM_Size (Target);
3768
3769                if Source_Siz /= Target_Siz then
3770                   Error_Msg_N
3771                     ("types for unchecked conversion have different sizes?",
3772                      Enode);
3773
3774                   if All_Errors_Mode then
3775                      Error_Msg_Name_1 := Chars (Source);
3776                      Error_Msg_Uint_1 := Source_Siz;
3777                      Error_Msg_Name_2 := Chars (Target);
3778                      Error_Msg_Uint_2 := Target_Siz;
3779                      Error_Msg_N
3780                        ("\size of % is ^, size of % is ^?", Enode);
3781
3782                      Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
3783
3784                      if Is_Discrete_Type (Source)
3785                        and then Is_Discrete_Type (Target)
3786                      then
3787                         if Source_Siz > Target_Siz then
3788                            Error_Msg_N
3789                              ("\^ high order bits of source will be ignored?",
3790                               Enode);
3791
3792                         elsif Is_Unsigned_Type (Source) then
3793                            Error_Msg_N
3794                              ("\source will be extended with ^ high order " &
3795                               "zero bits?", Enode);
3796
3797                         else
3798                            Error_Msg_N
3799                              ("\source will be extended with ^ high order " &
3800                               "sign bits?",
3801                               Enode);
3802                         end if;
3803
3804                      elsif Source_Siz < Target_Siz then
3805                         if Is_Discrete_Type (Target) then
3806                            if Bytes_Big_Endian then
3807                               Error_Msg_N
3808                                 ("\target value will include ^ undefined " &
3809                                  "low order bits?",
3810                                  Enode);
3811                            else
3812                               Error_Msg_N
3813                                 ("\target value will include ^ undefined " &
3814                                  "high order bits?",
3815                                  Enode);
3816                            end if;
3817
3818                         else
3819                            Error_Msg_N
3820                              ("\^ trailing bits of target value will be " &
3821                               "undefined?", Enode);
3822                         end if;
3823
3824                      else pragma Assert (Source_Siz > Target_Siz);
3825                         Error_Msg_N
3826                           ("\^ trailing bits of source will be ignored?",
3827                            Enode);
3828                      end if;
3829                   end if;
3830                end if;
3831             end if;
3832
3833             --  If both types are access types, we need to check the alignment.
3834             --  If the alignment of both is specified, we can do it here.
3835
3836             if Serious_Errors_Detected = 0
3837               and then Ekind (Source) in Access_Kind
3838               and then Ekind (Target) in Access_Kind
3839               and then Target_Strict_Alignment
3840               and then Present (Designated_Type (Source))
3841               and then Present (Designated_Type (Target))
3842             then
3843                declare
3844                   D_Source : constant Entity_Id := Designated_Type (Source);
3845                   D_Target : constant Entity_Id := Designated_Type (Target);
3846
3847                begin
3848                   if Known_Alignment (D_Source)
3849                     and then Known_Alignment (D_Target)
3850                   then
3851                      declare
3852                         Source_Align : constant Uint := Alignment (D_Source);
3853                         Target_Align : constant Uint := Alignment (D_Target);
3854
3855                      begin
3856                         if Source_Align < Target_Align
3857                           and then not Is_Tagged_Type (D_Source)
3858                         then
3859                            Error_Msg_Uint_1 := Target_Align;
3860                            Error_Msg_Uint_2 := Source_Align;
3861                            Error_Msg_Node_2 := D_Source;
3862                            Error_Msg_NE
3863                              ("alignment of & (^) is stricter than " &
3864                               "alignment of & (^)?", Enode, D_Target);
3865
3866                            if All_Errors_Mode then
3867                               Error_Msg_N
3868                                 ("\resulting access value may have invalid " &
3869                                  "alignment?", Enode);
3870                            end if;
3871                         end if;
3872                      end;
3873                   end if;
3874                end;
3875             end if;
3876          end;
3877       end loop;
3878    end Validate_Unchecked_Conversions;
3879
3880 end Sem_Ch13;