OSDN Git Service

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