OSDN Git Service

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