OSDN Git Service

903aad050a3239645abdb49745cfcd27fd6107b6
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_attr.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             S E M _ A T T R                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2007, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license.          --
20 --                                                                          --
21 -- GNAT was originally developed  by the GNAT team at  New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
23 --                                                                          --
24 ------------------------------------------------------------------------------
25
26 with Ada.Characters.Latin_1; use Ada.Characters.Latin_1;
27
28 with Atree;    use Atree;
29 with Casing;   use Casing;
30 with Checks;   use Checks;
31 with Einfo;    use Einfo;
32 with Errout;   use Errout;
33 with Eval_Fat;
34 with Exp_Dist; use Exp_Dist;
35 with Exp_Util; use Exp_Util;
36 with Expander; use Expander;
37 with Freeze;   use Freeze;
38 with Lib;      use Lib;
39 with Lib.Xref; use Lib.Xref;
40 with Nlists;   use Nlists;
41 with Nmake;    use Nmake;
42 with Opt;      use Opt;
43 with Restrict; use Restrict;
44 with Rident;   use Rident;
45 with Rtsfind;  use Rtsfind;
46 with Sdefault; use Sdefault;
47 with Sem;      use Sem;
48 with Sem_Cat;  use Sem_Cat;
49 with Sem_Ch6;  use Sem_Ch6;
50 with Sem_Ch8;  use Sem_Ch8;
51 with Sem_Dist; use Sem_Dist;
52 with Sem_Eval; use Sem_Eval;
53 with Sem_Res;  use Sem_Res;
54 with Sem_Type; use Sem_Type;
55 with Sem_Util; use Sem_Util;
56 with Stand;    use Stand;
57 with Sinfo;    use Sinfo;
58 with Sinput;   use Sinput;
59 with Stringt;  use Stringt;
60 with Style;
61 with Stylesw;  use Stylesw;
62 with Targparm; use Targparm;
63 with Ttypes;   use Ttypes;
64 with Ttypef;   use Ttypef;
65 with Tbuild;   use Tbuild;
66 with Uintp;    use Uintp;
67 with Urealp;   use Urealp;
68
69 package body Sem_Attr is
70
71    True_Value  : constant Uint := Uint_1;
72    False_Value : constant Uint := Uint_0;
73    --  Synonyms to be used when these constants are used as Boolean values
74
75    Bad_Attribute : exception;
76    --  Exception raised if an error is detected during attribute processing,
77    --  used so that we can abandon the processing so we don't run into
78    --  trouble with cascaded errors.
79
80    --  The following array is the list of attributes defined in the Ada 83 RM
81    --  that are not included in Ada 95, but still get recognized in GNAT.
82
83    Attribute_83 : constant Attribute_Class_Array := Attribute_Class_Array'(
84       Attribute_Address           |
85       Attribute_Aft               |
86       Attribute_Alignment         |
87       Attribute_Base              |
88       Attribute_Callable          |
89       Attribute_Constrained       |
90       Attribute_Count             |
91       Attribute_Delta             |
92       Attribute_Digits            |
93       Attribute_Emax              |
94       Attribute_Epsilon           |
95       Attribute_First             |
96       Attribute_First_Bit         |
97       Attribute_Fore              |
98       Attribute_Image             |
99       Attribute_Large             |
100       Attribute_Last              |
101       Attribute_Last_Bit          |
102       Attribute_Leading_Part      |
103       Attribute_Length            |
104       Attribute_Machine_Emax      |
105       Attribute_Machine_Emin      |
106       Attribute_Machine_Mantissa  |
107       Attribute_Machine_Overflows |
108       Attribute_Machine_Radix     |
109       Attribute_Machine_Rounds    |
110       Attribute_Mantissa          |
111       Attribute_Pos               |
112       Attribute_Position          |
113       Attribute_Pred              |
114       Attribute_Range             |
115       Attribute_Safe_Emax         |
116       Attribute_Safe_Large        |
117       Attribute_Safe_Small        |
118       Attribute_Size              |
119       Attribute_Small             |
120       Attribute_Storage_Size      |
121       Attribute_Succ              |
122       Attribute_Terminated        |
123       Attribute_Val               |
124       Attribute_Value             |
125       Attribute_Width             => True,
126       others                      => False);
127
128    --  The following array is the list of attributes defined in the Ada 2005
129    --  RM which are not defined in Ada 95. These are recognized in Ada 95 mode,
130    --  but in Ada 95 they are considered to be implementation defined.
131
132    Attribute_05 : constant Attribute_Class_Array := Attribute_Class_Array'(
133       Attribute_Machine_Rounding  |
134       Attribute_Priority          |
135       Attribute_Stream_Size       |
136       Attribute_Wide_Wide_Width   => True,
137       others                      => False);
138
139    --  The following array contains all attributes that imply a modification
140    --  of their prefixes or result in an access value. Such prefixes can be
141    --  considered as lvalues.
142
143    Attribute_Name_Implies_Lvalue_Prefix : constant Attribute_Class_Array :=
144       Attribute_Class_Array'(
145       Attribute_Access              |
146       Attribute_Address             |
147       Attribute_Input               |
148       Attribute_Read                |
149       Attribute_Unchecked_Access    |
150       Attribute_Unrestricted_Access => True,
151       others                        => False);
152
153    -----------------------
154    -- Local_Subprograms --
155    -----------------------
156
157    procedure Eval_Attribute (N : Node_Id);
158    --  Performs compile time evaluation of attributes where possible, leaving
159    --  the Is_Static_Expression/Raises_Constraint_Error flags appropriately
160    --  set, and replacing the node with a literal node if the value can be
161    --  computed at compile time. All static attribute references are folded,
162    --  as well as a number of cases of non-static attributes that can always
163    --  be computed at compile time (e.g. floating-point model attributes that
164    --  are applied to non-static subtypes). Of course in such cases, the
165    --  Is_Static_Expression flag will not be set on the resulting literal.
166    --  Note that the only required action of this procedure is to catch the
167    --  static expression cases as described in the RM. Folding of other cases
168    --  is done where convenient, but some additional non-static folding is in
169    --  N_Expand_Attribute_Reference in cases where this is more convenient.
170
171    function Is_Anonymous_Tagged_Base
172      (Anon : Entity_Id;
173       Typ  : Entity_Id)
174       return Boolean;
175    --  For derived tagged types that constrain parent discriminants we build
176    --  an anonymous unconstrained base type. We need to recognize the relation
177    --  between the two when analyzing an access attribute for a constrained
178    --  component, before the full declaration for Typ has been analyzed, and
179    --  where therefore the prefix of the attribute does not match the enclosing
180    --  scope.
181
182    -----------------------
183    -- Analyze_Attribute --
184    -----------------------
185
186    procedure Analyze_Attribute (N : Node_Id) is
187       Loc     : constant Source_Ptr   := Sloc (N);
188       Aname   : constant Name_Id      := Attribute_Name (N);
189       P       : constant Node_Id      := Prefix (N);
190       Exprs   : constant List_Id      := Expressions (N);
191       Attr_Id : constant Attribute_Id := Get_Attribute_Id (Aname);
192       E1      : Node_Id;
193       E2      : Node_Id;
194
195       P_Type : Entity_Id;
196       --  Type of prefix after analysis
197
198       P_Base_Type : Entity_Id;
199       --  Base type of prefix after analysis
200
201       -----------------------
202       -- Local Subprograms --
203       -----------------------
204
205       procedure Analyze_Access_Attribute;
206       --  Used for Access, Unchecked_Access, Unrestricted_Access attributes.
207       --  Internally, Id distinguishes which of the three cases is involved.
208
209       procedure Check_Array_Or_Scalar_Type;
210       --  Common procedure used by First, Last, Range attribute to check
211       --  that the prefix is a constrained array or scalar type, or a name
212       --  of an array object, and that an argument appears only if appropriate
213       --  (i.e. only in the array case).
214
215       procedure Check_Array_Type;
216       --  Common semantic checks for all array attributes. Checks that the
217       --  prefix is a constrained array type or the name of an array object.
218       --  The error message for non-arrays is specialized appropriately.
219
220       procedure Check_Asm_Attribute;
221       --  Common semantic checks for Asm_Input and Asm_Output attributes
222
223       procedure Check_Component;
224       --  Common processing for Bit_Position, First_Bit, Last_Bit, and
225       --  Position. Checks prefix is an appropriate selected component.
226
227       procedure Check_Decimal_Fixed_Point_Type;
228       --  Check that prefix of attribute N is a decimal fixed-point type
229
230       procedure Check_Dereference;
231       --  If the prefix of attribute is an object of an access type, then
232       --  introduce an explicit deference, and adjust P_Type accordingly.
233
234       procedure Check_Discrete_Type;
235       --  Verify that prefix of attribute N is a discrete type
236
237       procedure Check_E0;
238       --  Check that no attribute arguments are present
239
240       procedure Check_Either_E0_Or_E1;
241       --  Check that there are zero or one attribute arguments present
242
243       procedure Check_E1;
244       --  Check that exactly one attribute argument is present
245
246       procedure Check_E2;
247       --  Check that two attribute arguments are present
248
249       procedure Check_Enum_Image;
250       --  If the prefix type is an enumeration type, set all its literals
251       --  as referenced, since the image function could possibly end up
252       --  referencing any of the literals indirectly.
253
254       procedure Check_Fixed_Point_Type;
255       --  Verify that prefix of attribute N is a fixed type
256
257       procedure Check_Fixed_Point_Type_0;
258       --  Verify that prefix of attribute N is a fixed type and that
259       --  no attribute expressions are present
260
261       procedure Check_Floating_Point_Type;
262       --  Verify that prefix of attribute N is a float type
263
264       procedure Check_Floating_Point_Type_0;
265       --  Verify that prefix of attribute N is a float type and that
266       --  no attribute expressions are present
267
268       procedure Check_Floating_Point_Type_1;
269       --  Verify that prefix of attribute N is a float type and that
270       --  exactly one attribute expression is present
271
272       procedure Check_Floating_Point_Type_2;
273       --  Verify that prefix of attribute N is a float type and that
274       --  two attribute expressions are present
275
276       procedure Legal_Formal_Attribute;
277       --  Common processing for attributes Definite, Has_Access_Values,
278       --  and Has_Discriminants
279
280       procedure Check_Integer_Type;
281       --  Verify that prefix of attribute N is an integer type
282
283       procedure Check_Library_Unit;
284       --  Verify that prefix of attribute N is a library unit
285
286       procedure Check_Modular_Integer_Type;
287       --  Verify that prefix of attribute N is a modular integer type
288
289       procedure Check_Not_Incomplete_Type;
290       --  Check that P (the prefix of the attribute) is not an incomplete
291       --  type or a private type for which no full view has been given.
292
293       procedure Check_Object_Reference (P : Node_Id);
294       --  Check that P (the prefix of the attribute) is an object reference
295
296       procedure Check_Program_Unit;
297       --  Verify that prefix of attribute N is a program unit
298
299       procedure Check_Real_Type;
300       --  Verify that prefix of attribute N is fixed or float type
301
302       procedure Check_Scalar_Type;
303       --  Verify that prefix of attribute N is a scalar type
304
305       procedure Check_Standard_Prefix;
306       --  Verify that prefix of attribute N is package Standard
307
308       procedure Check_Stream_Attribute (Nam : TSS_Name_Type);
309       --  Validity checking for stream attribute. Nam is the TSS name of the
310       --  corresponding possible defined attribute function (e.g. for the
311       --  Read attribute, Nam will be TSS_Stream_Read).
312
313       procedure Check_Task_Prefix;
314       --  Verify that prefix of attribute N is a task or task type
315
316       procedure Check_Type;
317       --  Verify that the prefix of attribute N is a type
318
319       procedure Check_Unit_Name (Nod : Node_Id);
320       --  Check that Nod is of the form of a library unit name, i.e that
321       --  it is an identifier, or a selected component whose prefix is
322       --  itself of the form of a library unit name. Note that this is
323       --  quite different from Check_Program_Unit, since it only checks
324       --  the syntactic form of the name, not the semantic identity. This
325       --  is because it is used with attributes (Elab_Body, Elab_Spec, and
326       --  UET_Address) which can refer to non-visible unit.
327
328       procedure Error_Attr (Msg : String; Error_Node : Node_Id);
329       pragma No_Return (Error_Attr);
330       procedure Error_Attr;
331       pragma No_Return (Error_Attr);
332       --  Posts error using Error_Msg_N at given node, sets type of attribute
333       --  node to Any_Type, and then raises Bad_Attribute to avoid any further
334       --  semantic processing. The message typically contains a % insertion
335       --  character which is replaced by the attribute name. The call with
336       --  no arguments is used when the caller has already generated the
337       --  required error messages.
338
339       procedure Error_Attr_P (Msg : String);
340       pragma No_Return (Error_Attr);
341       --  Like Error_Attr, but error is posted at the start of the prefix
342
343       procedure Standard_Attribute (Val : Int);
344       --  Used to process attributes whose prefix is package Standard which
345       --  yield values of type Universal_Integer. The attribute reference
346       --  node is rewritten with an integer literal of the given value.
347
348       procedure Unexpected_Argument (En : Node_Id);
349       --  Signal unexpected attribute argument (En is the argument)
350
351       procedure Validate_Non_Static_Attribute_Function_Call;
352       --  Called when processing an attribute that is a function call to a
353       --  non-static function, i.e. an attribute function that either takes
354       --  non-scalar arguments or returns a non-scalar result. Verifies that
355       --  such a call does not appear in a preelaborable context.
356
357       ------------------------------
358       -- Analyze_Access_Attribute --
359       ------------------------------
360
361       procedure Analyze_Access_Attribute is
362          Acc_Type : Entity_Id;
363
364          Scop : Entity_Id;
365          Typ  : Entity_Id;
366
367          function Build_Access_Object_Type (DT : Entity_Id) return Entity_Id;
368          --  Build an access-to-object type whose designated type is DT,
369          --  and whose Ekind is appropriate to the attribute type. The
370          --  type that is constructed is returned as the result.
371
372          procedure Build_Access_Subprogram_Type (P : Node_Id);
373          --  Build an access to subprogram whose designated type is
374          --  the type of the prefix. If prefix is overloaded, so it the
375          --  node itself. The result is stored in Acc_Type.
376
377          function OK_Self_Reference return Boolean;
378          --  An access reference whose prefix is a type can legally appear
379          --  within an aggregate, where it is obtained by expansion of
380          --  a defaulted aggregate. The enclosing aggregate that contains
381          --  the self-referenced is flagged so that the self-reference can
382          --  be expanded into a reference to the target object (see exp_aggr).
383
384          ------------------------------
385          -- Build_Access_Object_Type --
386          ------------------------------
387
388          function Build_Access_Object_Type (DT : Entity_Id) return Entity_Id is
389             Typ : constant Entity_Id :=
390                     New_Internal_Entity
391                       (E_Access_Attribute_Type, Current_Scope, Loc, 'A');
392          begin
393             Set_Etype                     (Typ, Typ);
394             Init_Size_Align               (Typ);
395             Set_Is_Itype                  (Typ);
396             Set_Associated_Node_For_Itype (Typ, N);
397             Set_Directly_Designated_Type  (Typ, DT);
398             return Typ;
399          end Build_Access_Object_Type;
400
401          ----------------------------------
402          -- Build_Access_Subprogram_Type --
403          ----------------------------------
404
405          procedure Build_Access_Subprogram_Type (P : Node_Id) is
406             Index : Interp_Index;
407             It    : Interp;
408
409             procedure Check_Local_Access (E : Entity_Id);
410             --  Deal with possible access to local subprogram. If we have such
411             --  an access, we set a flag to kill all tracked values on any call
412             --  because this access value may be passed around, and any called
413             --  code might use it to access a local procedure which clobbers a
414             --  tracked value.
415
416             function Get_Kind (E : Entity_Id) return Entity_Kind;
417             --  Distinguish between access to regular/protected subprograms
418
419             ------------------------
420             -- Check_Local_Access --
421             ------------------------
422
423             procedure Check_Local_Access (E : Entity_Id) is
424             begin
425                if not Is_Library_Level_Entity (E) then
426                   Set_Suppress_Value_Tracking_On_Call (Current_Scope);
427                end if;
428             end Check_Local_Access;
429
430             --------------
431             -- Get_Kind --
432             --------------
433
434             function Get_Kind (E : Entity_Id) return Entity_Kind is
435             begin
436                if Convention (E) = Convention_Protected then
437                   return E_Access_Protected_Subprogram_Type;
438                else
439                   return E_Access_Subprogram_Type;
440                end if;
441             end Get_Kind;
442
443          --  Start of processing for Build_Access_Subprogram_Type
444
445          begin
446             --  In the case of an access to subprogram, use the name of the
447             --  subprogram itself as the designated type. Type-checking in
448             --  this case compares the signatures of the designated types.
449
450             Set_Etype (N, Any_Type);
451
452             if not Is_Overloaded (P) then
453                Check_Local_Access (Entity (P));
454
455                if not Is_Intrinsic_Subprogram (Entity (P)) then
456                   Acc_Type :=
457                     New_Internal_Entity
458                       (Get_Kind (Entity (P)), Current_Scope, Loc, 'A');
459                   Set_Etype (Acc_Type, Acc_Type);
460                   Set_Directly_Designated_Type (Acc_Type, Entity (P));
461                   Set_Etype (N, Acc_Type);
462                end if;
463
464             else
465                Get_First_Interp (P, Index, It);
466                while Present (It.Nam) loop
467                   Check_Local_Access (It.Nam);
468
469                   if not Is_Intrinsic_Subprogram (It.Nam) then
470                      Acc_Type :=
471                        New_Internal_Entity
472                          (Get_Kind (It.Nam), Current_Scope, Loc, 'A');
473                      Set_Etype (Acc_Type, Acc_Type);
474                      Set_Directly_Designated_Type (Acc_Type, It.Nam);
475                      Add_One_Interp (N, Acc_Type, Acc_Type);
476                   end if;
477
478                   Get_Next_Interp (Index, It);
479                end loop;
480             end if;
481
482             --  Cannot be applied to intrinsic. Looking at the tests above,
483             --  the only way Etype (N) can still be set to Any_Type is if
484             --  Is_Intrinsic_Subprogram was True for some referenced entity.
485
486             if Etype (N) = Any_Type then
487                Error_Attr_P ("prefix of % attribute cannot be intrinsic");
488             end if;
489          end Build_Access_Subprogram_Type;
490
491          ----------------------
492          -- OK_Self_Reference --
493          ----------------------
494
495          function OK_Self_Reference return Boolean is
496             Par : Node_Id;
497
498          begin
499             Par := Parent (N);
500             while Present (Par)
501               and then
502                (Nkind (Par) = N_Component_Association
503                  or else Nkind (Par) in N_Subexpr)
504             loop
505                if Nkind (Par) = N_Aggregate
506                  or else Nkind (Par) = N_Extension_Aggregate
507                then
508                   if Etype (Par) = Typ then
509                      Set_Has_Self_Reference (Par);
510                      return True;
511                   end if;
512                end if;
513
514                Par := Parent (Par);
515             end loop;
516
517             --  No enclosing aggregate, or not a self-reference
518
519             return False;
520          end OK_Self_Reference;
521
522       --  Start of processing for Analyze_Access_Attribute
523
524       begin
525          Check_E0;
526
527          if Nkind (P) = N_Character_Literal then
528             Error_Attr_P
529               ("prefix of % attribute cannot be enumeration literal");
530          end if;
531
532          --  Case of access to subprogram
533
534          if Is_Entity_Name (P)
535            and then Is_Overloadable (Entity (P))
536          then
537             --  Not allowed for nested subprograms if No_Implicit_Dynamic_Code
538             --  restriction set (since in general a trampoline is required).
539
540             if not Is_Library_Level_Entity (Entity (P)) then
541                Check_Restriction (No_Implicit_Dynamic_Code, P);
542             end if;
543
544             if Is_Always_Inlined (Entity (P)) then
545                Error_Attr_P
546                  ("prefix of % attribute cannot be Inline_Always subprogram");
547             end if;
548
549             if Aname = Name_Unchecked_Access then
550                Error_Attr ("attribute% cannot be applied to a subprogram", P);
551             end if;
552
553             --  Build the appropriate subprogram type
554
555             Build_Access_Subprogram_Type (P);
556
557             --  For unrestricted access, kill current values, since this
558             --  attribute allows a reference to a local subprogram that
559             --  could modify local variables to be passed out of scope
560
561             if Aname = Name_Unrestricted_Access then
562                Kill_Current_Values;
563             end if;
564
565             return;
566
567          --  Component is an operation of a protected type
568
569          elsif Nkind (P) = N_Selected_Component
570            and then Is_Overloadable (Entity (Selector_Name (P)))
571          then
572             if Ekind (Entity (Selector_Name (P))) = E_Entry then
573                Error_Attr_P ("prefix of % attribute must be subprogram");
574             end if;
575
576             Build_Access_Subprogram_Type (Selector_Name (P));
577             return;
578          end if;
579
580          --  Deal with incorrect reference to a type, but note that some
581          --  accesses are allowed: references to the current type instance,
582          --  or in Ada 2005 self-referential pointer in a default-initialized
583          --  aggregate.
584
585          if Is_Entity_Name (P) then
586             Typ := Entity (P);
587
588             --  The reference may appear in an aggregate that has been expanded
589             --  into a loop. Locate scope of type definition, if any.
590
591             Scop := Current_Scope;
592             while Ekind (Scop) = E_Loop loop
593                Scop := Scope (Scop);
594             end loop;
595
596             if Is_Type (Typ) then
597
598                --  OK if we are within the scope of a limited type
599                --  let's mark the component as having per object constraint
600
601                if Is_Anonymous_Tagged_Base (Scop, Typ) then
602                   Typ := Scop;
603                   Set_Entity (P, Typ);
604                   Set_Etype  (P, Typ);
605                end if;
606
607                if Typ = Scop then
608                   declare
609                      Q : Node_Id := Parent (N);
610
611                   begin
612                      while Present (Q)
613                        and then Nkind (Q) /= N_Component_Declaration
614                      loop
615                         Q := Parent (Q);
616                      end loop;
617
618                      if Present (Q) then
619                         Set_Has_Per_Object_Constraint (
620                           Defining_Identifier (Q), True);
621                      end if;
622                   end;
623
624                   if Nkind (P) = N_Expanded_Name then
625                      Error_Msg_F
626                        ("current instance prefix must be a direct name", P);
627                   end if;
628
629                   --  If a current instance attribute appears within a
630                   --  a component constraint it must appear alone; other
631                   --  contexts (default expressions, within a task body)
632                   --  are not subject to this restriction.
633
634                   if not In_Default_Expression
635                     and then not Has_Completion (Scop)
636                     and then
637                       Nkind (Parent (N)) /= N_Discriminant_Association
638                     and then
639                       Nkind (Parent (N)) /= N_Index_Or_Discriminant_Constraint
640                   then
641                      Error_Msg_N
642                        ("current instance attribute must appear alone", N);
643                   end if;
644
645                --  OK if we are in initialization procedure for the type
646                --  in question, in which case the reference to the type
647                --  is rewritten as a reference to the current object.
648
649                elsif Ekind (Scop) = E_Procedure
650                  and then Is_Init_Proc (Scop)
651                  and then Etype (First_Formal (Scop)) = Typ
652                then
653                   Rewrite (N,
654                     Make_Attribute_Reference (Loc,
655                       Prefix         => Make_Identifier (Loc, Name_uInit),
656                       Attribute_Name => Name_Unrestricted_Access));
657                   Analyze (N);
658                   return;
659
660                --  OK if a task type, this test needs sharpening up ???
661
662                elsif Is_Task_Type (Typ) then
663                   null;
664
665                --  OK if self-reference in an aggregate in Ada 2005, and
666                --  the reference comes from a copied default expression.
667
668                --  Note that we check legality of self-reference even if the
669                --  expression comes from source, e.g. when a single component
670                --  association in an aggregate has a box association.
671
672                elsif Ada_Version >= Ada_05
673                  and then OK_Self_Reference
674                then
675                   null;
676
677                --  Otherwise we have an error case
678
679                else
680                   Error_Attr ("% attribute cannot be applied to type", P);
681                   return;
682                end if;
683             end if;
684          end if;
685
686          --  If we fall through, we have a normal access to object case.
687          --  Unrestricted_Access is legal wherever an allocator would be
688          --  legal, so its Etype is set to E_Allocator. The expected type
689          --  of the other attributes is a general access type, and therefore
690          --  we label them with E_Access_Attribute_Type.
691
692          if not Is_Overloaded (P) then
693             Acc_Type := Build_Access_Object_Type (P_Type);
694             Set_Etype (N, Acc_Type);
695          else
696             declare
697                Index : Interp_Index;
698                It    : Interp;
699             begin
700                Set_Etype (N, Any_Type);
701                Get_First_Interp (P, Index, It);
702                while Present (It.Typ) loop
703                   Acc_Type := Build_Access_Object_Type (It.Typ);
704                   Add_One_Interp (N, Acc_Type, Acc_Type);
705                   Get_Next_Interp (Index, It);
706                end loop;
707             end;
708          end if;
709
710          --  Special cases when we can find a prefix that is an entity name
711
712          declare
713             PP  : Node_Id;
714             Ent : Entity_Id;
715
716          begin
717             PP := P;
718             loop
719                if Is_Entity_Name (PP) then
720                   Ent := Entity (PP);
721
722                   --  If we have an access to an object, and the attribute
723                   --  comes from source, then set the object as potentially
724                   --  source modified. We do this because the resulting access
725                   --  pointer can be used to modify the variable, and we might
726                   --  not detect this, leading to some junk warnings.
727
728                   Set_Never_Set_In_Source (Ent, False);
729
730                   --  Mark entity as address taken, and kill current values
731
732                   Set_Address_Taken (Ent);
733                   Kill_Current_Values (Ent);
734                   exit;
735
736                elsif Nkind (PP) = N_Selected_Component
737                  or else Nkind (PP) = N_Indexed_Component
738                then
739                   PP := Prefix (PP);
740
741                else
742                   exit;
743                end if;
744             end loop;
745          end;
746
747          --  Check for aliased view unless unrestricted case. We allow a
748          --  nonaliased prefix when within an instance because the prefix may
749          --  have been a tagged formal object, which is defined to be aliased
750          --  even when the actual might not be (other instance cases will have
751          --  been caught in the generic). Similarly, within an inlined body we
752          --  know that the attribute is legal in the original subprogram, and
753          --  therefore legal in the expansion.
754
755          if Aname /= Name_Unrestricted_Access
756            and then not Is_Aliased_View (P)
757            and then not In_Instance
758            and then not In_Inlined_Body
759          then
760             Error_Attr_P ("prefix of % attribute must be aliased");
761          end if;
762       end Analyze_Access_Attribute;
763
764       --------------------------------
765       -- Check_Array_Or_Scalar_Type --
766       --------------------------------
767
768       procedure Check_Array_Or_Scalar_Type is
769          Index : Entity_Id;
770
771          D : Int;
772          --  Dimension number for array attributes
773
774       begin
775          --  Case of string literal or string literal subtype. These cases
776          --  cannot arise from legal Ada code, but the expander is allowed
777          --  to generate them. They require special handling because string
778          --  literal subtypes do not have standard bounds (the whole idea
779          --  of these subtypes is to avoid having to generate the bounds)
780
781          if Ekind (P_Type) = E_String_Literal_Subtype then
782             Set_Etype (N, Etype (First_Index (P_Base_Type)));
783             return;
784
785          --  Scalar types
786
787          elsif Is_Scalar_Type (P_Type) then
788             Check_Type;
789
790             if Present (E1) then
791                Error_Attr ("invalid argument in % attribute", E1);
792             else
793                Set_Etype (N, P_Base_Type);
794                return;
795             end if;
796
797          --  The following is a special test to allow 'First to apply to
798          --  private scalar types if the attribute comes from generated
799          --  code. This occurs in the case of Normalize_Scalars code.
800
801          elsif Is_Private_Type (P_Type)
802            and then Present (Full_View (P_Type))
803            and then Is_Scalar_Type (Full_View (P_Type))
804            and then not Comes_From_Source (N)
805          then
806             Set_Etype (N, Implementation_Base_Type (P_Type));
807
808          --  Array types other than string literal subtypes handled above
809
810          else
811             Check_Array_Type;
812
813             --  We know prefix is an array type, or the name of an array
814             --  object, and that the expression, if present, is static
815             --  and within the range of the dimensions of the type.
816
817             pragma Assert (Is_Array_Type (P_Type));
818             Index := First_Index (P_Base_Type);
819
820             if No (E1) then
821
822                --  First dimension assumed
823
824                Set_Etype (N, Base_Type (Etype (Index)));
825
826             else
827                D := UI_To_Int (Intval (E1));
828
829                for J in 1 .. D - 1 loop
830                   Next_Index (Index);
831                end loop;
832
833                Set_Etype (N, Base_Type (Etype (Index)));
834                Set_Etype (E1, Standard_Integer);
835             end if;
836          end if;
837       end Check_Array_Or_Scalar_Type;
838
839       ----------------------
840       -- Check_Array_Type --
841       ----------------------
842
843       procedure Check_Array_Type is
844          D : Int;
845          --  Dimension number for array attributes
846
847       begin
848          --  If the type is a string literal type, then this must be generated
849          --  internally, and no further check is required on its legality.
850
851          if Ekind (P_Type) = E_String_Literal_Subtype then
852             return;
853
854          --  If the type is a composite, it is an illegal aggregate, no point
855          --  in going on.
856
857          elsif P_Type = Any_Composite then
858             raise Bad_Attribute;
859          end if;
860
861          --  Normal case of array type or subtype
862
863          Check_Either_E0_Or_E1;
864          Check_Dereference;
865
866          if Is_Array_Type (P_Type) then
867             if not Is_Constrained (P_Type)
868               and then Is_Entity_Name (P)
869               and then Is_Type (Entity (P))
870             then
871                --  Note: we do not call Error_Attr here, since we prefer to
872                --  continue, using the relevant index type of the array,
873                --  even though it is unconstrained. This gives better error
874                --  recovery behavior.
875
876                Error_Msg_Name_1 := Aname;
877                Error_Msg_F
878                  ("prefix for % attribute must be constrained array", P);
879             end if;
880
881             D := Number_Dimensions (P_Type);
882
883          else
884             if Is_Private_Type (P_Type) then
885                Error_Attr_P ("prefix for % attribute may not be private type");
886
887             elsif Is_Access_Type (P_Type)
888               and then Is_Array_Type (Designated_Type (P_Type))
889               and then Is_Entity_Name (P)
890               and then Is_Type (Entity (P))
891             then
892                Error_Attr_P ("prefix of % attribute cannot be access type");
893
894             elsif Attr_Id = Attribute_First
895                     or else
896                   Attr_Id = Attribute_Last
897             then
898                Error_Attr ("invalid prefix for % attribute", P);
899
900             else
901                Error_Attr_P ("prefix for % attribute must be array");
902             end if;
903          end if;
904
905          if Present (E1) then
906             Resolve (E1, Any_Integer);
907             Set_Etype (E1, Standard_Integer);
908
909             if not Is_Static_Expression (E1)
910               or else Raises_Constraint_Error (E1)
911             then
912                Flag_Non_Static_Expr
913                  ("expression for dimension must be static!", E1);
914                Error_Attr;
915
916             elsif  UI_To_Int (Expr_Value (E1)) > D
917               or else UI_To_Int (Expr_Value (E1)) < 1
918             then
919                Error_Attr ("invalid dimension number for array type", E1);
920             end if;
921          end if;
922
923          if (Style_Check and Style_Check_Array_Attribute_Index)
924            and then Comes_From_Source (N)
925          then
926             Style.Check_Array_Attribute_Index (N, E1, D);
927          end if;
928       end Check_Array_Type;
929
930       -------------------------
931       -- Check_Asm_Attribute --
932       -------------------------
933
934       procedure Check_Asm_Attribute is
935       begin
936          Check_Type;
937          Check_E2;
938
939          --  Check first argument is static string expression
940
941          Analyze_And_Resolve (E1, Standard_String);
942
943          if Etype (E1) = Any_Type then
944             return;
945
946          elsif not Is_OK_Static_Expression (E1) then
947             Flag_Non_Static_Expr
948               ("constraint argument must be static string expression!", E1);
949             Error_Attr;
950          end if;
951
952          --  Check second argument is right type
953
954          Analyze_And_Resolve (E2, Entity (P));
955
956          --  Note: that is all we need to do, we don't need to check
957          --  that it appears in a correct context. The Ada type system
958          --  will do that for us.
959
960       end Check_Asm_Attribute;
961
962       ---------------------
963       -- Check_Component --
964       ---------------------
965
966       procedure Check_Component is
967       begin
968          Check_E0;
969
970          if Nkind (P) /= N_Selected_Component
971            or else
972              (Ekind (Entity (Selector_Name (P))) /= E_Component
973                and then
974               Ekind (Entity (Selector_Name (P))) /= E_Discriminant)
975          then
976             Error_Attr_P ("prefix for % attribute must be selected component");
977          end if;
978       end Check_Component;
979
980       ------------------------------------
981       -- Check_Decimal_Fixed_Point_Type --
982       ------------------------------------
983
984       procedure Check_Decimal_Fixed_Point_Type is
985       begin
986          Check_Type;
987
988          if not Is_Decimal_Fixed_Point_Type (P_Type) then
989             Error_Attr_P ("prefix of % attribute must be decimal type");
990          end if;
991       end Check_Decimal_Fixed_Point_Type;
992
993       -----------------------
994       -- Check_Dereference --
995       -----------------------
996
997       procedure Check_Dereference is
998       begin
999
1000          --  Case of a subtype mark
1001
1002          if Is_Entity_Name (P)
1003            and then Is_Type (Entity (P))
1004          then
1005             return;
1006          end if;
1007
1008          --  Case of an expression
1009
1010          Resolve (P);
1011
1012          if Is_Access_Type (P_Type) then
1013
1014             --  If there is an implicit dereference, then we must freeze
1015             --  the designated type of the access type, since the type of
1016             --  the referenced array is this type (see AI95-00106).
1017
1018             Freeze_Before (N, Designated_Type (P_Type));
1019
1020             Rewrite (P,
1021               Make_Explicit_Dereference (Sloc (P),
1022                 Prefix => Relocate_Node (P)));
1023
1024             Analyze_And_Resolve (P);
1025             P_Type := Etype (P);
1026
1027             if P_Type = Any_Type then
1028                raise Bad_Attribute;
1029             end if;
1030
1031             P_Base_Type := Base_Type (P_Type);
1032          end if;
1033       end Check_Dereference;
1034
1035       -------------------------
1036       -- Check_Discrete_Type --
1037       -------------------------
1038
1039       procedure Check_Discrete_Type is
1040       begin
1041          Check_Type;
1042
1043          if not Is_Discrete_Type (P_Type) then
1044             Error_Attr_P ("prefix of % attribute must be discrete type");
1045          end if;
1046       end Check_Discrete_Type;
1047
1048       --------------
1049       -- Check_E0 --
1050       --------------
1051
1052       procedure Check_E0 is
1053       begin
1054          if Present (E1) then
1055             Unexpected_Argument (E1);
1056          end if;
1057       end Check_E0;
1058
1059       --------------
1060       -- Check_E1 --
1061       --------------
1062
1063       procedure Check_E1 is
1064       begin
1065          Check_Either_E0_Or_E1;
1066
1067          if No (E1) then
1068
1069             --  Special-case attributes that are functions and that appear as
1070             --  the prefix of another attribute. Error is posted on parent.
1071
1072             if Nkind (Parent (N)) = N_Attribute_Reference
1073               and then (Attribute_Name (Parent (N)) = Name_Address
1074                           or else
1075                         Attribute_Name (Parent (N)) = Name_Code_Address
1076                           or else
1077                         Attribute_Name (Parent (N)) = Name_Access)
1078             then
1079                Error_Msg_Name_1 := Attribute_Name (Parent (N));
1080                Error_Msg_N ("illegal prefix for % attribute", Parent (N));
1081                Set_Etype (Parent (N), Any_Type);
1082                Set_Entity (Parent (N), Any_Type);
1083                raise Bad_Attribute;
1084
1085             else
1086                Error_Attr ("missing argument for % attribute", N);
1087             end if;
1088          end if;
1089       end Check_E1;
1090
1091       --------------
1092       -- Check_E2 --
1093       --------------
1094
1095       procedure Check_E2 is
1096       begin
1097          if No (E1) then
1098             Error_Attr ("missing arguments for % attribute (2 required)", N);
1099          elsif No (E2) then
1100             Error_Attr ("missing argument for % attribute (2 required)", N);
1101          end if;
1102       end Check_E2;
1103
1104       ---------------------------
1105       -- Check_Either_E0_Or_E1 --
1106       ---------------------------
1107
1108       procedure Check_Either_E0_Or_E1 is
1109       begin
1110          if Present (E2) then
1111             Unexpected_Argument (E2);
1112          end if;
1113       end Check_Either_E0_Or_E1;
1114
1115       ----------------------
1116       -- Check_Enum_Image --
1117       ----------------------
1118
1119       procedure Check_Enum_Image is
1120          Lit : Entity_Id;
1121       begin
1122          if Is_Enumeration_Type (P_Base_Type) then
1123             Lit := First_Literal (P_Base_Type);
1124             while Present (Lit) loop
1125                Set_Referenced (Lit);
1126                Next_Literal (Lit);
1127             end loop;
1128          end if;
1129       end Check_Enum_Image;
1130
1131       ----------------------------
1132       -- Check_Fixed_Point_Type --
1133       ----------------------------
1134
1135       procedure Check_Fixed_Point_Type is
1136       begin
1137          Check_Type;
1138
1139          if not Is_Fixed_Point_Type (P_Type) then
1140             Error_Attr_P ("prefix of % attribute must be fixed point type");
1141          end if;
1142       end Check_Fixed_Point_Type;
1143
1144       ------------------------------
1145       -- Check_Fixed_Point_Type_0 --
1146       ------------------------------
1147
1148       procedure Check_Fixed_Point_Type_0 is
1149       begin
1150          Check_Fixed_Point_Type;
1151          Check_E0;
1152       end Check_Fixed_Point_Type_0;
1153
1154       -------------------------------
1155       -- Check_Floating_Point_Type --
1156       -------------------------------
1157
1158       procedure Check_Floating_Point_Type is
1159       begin
1160          Check_Type;
1161
1162          if not Is_Floating_Point_Type (P_Type) then
1163             Error_Attr_P ("prefix of % attribute must be float type");
1164          end if;
1165       end Check_Floating_Point_Type;
1166
1167       ---------------------------------
1168       -- Check_Floating_Point_Type_0 --
1169       ---------------------------------
1170
1171       procedure Check_Floating_Point_Type_0 is
1172       begin
1173          Check_Floating_Point_Type;
1174          Check_E0;
1175       end Check_Floating_Point_Type_0;
1176
1177       ---------------------------------
1178       -- Check_Floating_Point_Type_1 --
1179       ---------------------------------
1180
1181       procedure Check_Floating_Point_Type_1 is
1182       begin
1183          Check_Floating_Point_Type;
1184          Check_E1;
1185       end Check_Floating_Point_Type_1;
1186
1187       ---------------------------------
1188       -- Check_Floating_Point_Type_2 --
1189       ---------------------------------
1190
1191       procedure Check_Floating_Point_Type_2 is
1192       begin
1193          Check_Floating_Point_Type;
1194          Check_E2;
1195       end Check_Floating_Point_Type_2;
1196
1197       ------------------------
1198       -- Check_Integer_Type --
1199       ------------------------
1200
1201       procedure Check_Integer_Type is
1202       begin
1203          Check_Type;
1204
1205          if not Is_Integer_Type (P_Type) then
1206             Error_Attr_P ("prefix of % attribute must be integer type");
1207          end if;
1208       end Check_Integer_Type;
1209
1210       ------------------------
1211       -- Check_Library_Unit --
1212       ------------------------
1213
1214       procedure Check_Library_Unit is
1215       begin
1216          if not Is_Compilation_Unit (Entity (P)) then
1217             Error_Attr_P ("prefix of % attribute must be library unit");
1218          end if;
1219       end Check_Library_Unit;
1220
1221       --------------------------------
1222       -- Check_Modular_Integer_Type --
1223       --------------------------------
1224
1225       procedure Check_Modular_Integer_Type is
1226       begin
1227          Check_Type;
1228
1229          if not Is_Modular_Integer_Type (P_Type) then
1230             Error_Attr_P
1231               ("prefix of % attribute must be modular integer type");
1232          end if;
1233       end Check_Modular_Integer_Type;
1234
1235       -------------------------------
1236       -- Check_Not_Incomplete_Type --
1237       -------------------------------
1238
1239       procedure Check_Not_Incomplete_Type is
1240          E   : Entity_Id;
1241          Typ : Entity_Id;
1242
1243       begin
1244          --  Ada 2005 (AI-50217, AI-326): If the prefix is an explicit
1245          --  dereference we have to check wrong uses of incomplete types
1246          --  (other wrong uses are checked at their freezing point).
1247
1248          --  Example 1: Limited-with
1249
1250          --    limited with Pkg;
1251          --    package P is
1252          --       type Acc is access Pkg.T;
1253          --       X : Acc;
1254          --       S : Integer := X.all'Size;                    -- ERROR
1255          --    end P;
1256
1257          --  Example 2: Tagged incomplete
1258
1259          --     type T is tagged;
1260          --     type Acc is access all T;
1261          --     X : Acc;
1262          --     S : constant Integer := X.all'Size;             -- ERROR
1263          --     procedure Q (Obj : Integer := X.all'Alignment); -- ERROR
1264
1265          if Ada_Version >= Ada_05
1266            and then Nkind (P) = N_Explicit_Dereference
1267          then
1268             E := P;
1269             while Nkind (E) = N_Explicit_Dereference loop
1270                E := Prefix (E);
1271             end loop;
1272
1273             if From_With_Type (Etype (E)) then
1274                Error_Attr_P
1275                  ("prefix of % attribute cannot be an incomplete type");
1276
1277             else
1278                if Is_Access_Type (Etype (E)) then
1279                   Typ := Directly_Designated_Type (Etype (E));
1280                else
1281                   Typ := Etype (E);
1282                end if;
1283
1284                if Ekind (Typ) = E_Incomplete_Type
1285                  and then No (Full_View (Typ))
1286                then
1287                   Error_Attr_P
1288                     ("prefix of % attribute cannot be an incomplete type");
1289                end if;
1290             end if;
1291          end if;
1292
1293          if not Is_Entity_Name (P)
1294            or else not Is_Type (Entity (P))
1295            or else In_Default_Expression
1296          then
1297             return;
1298          else
1299             Check_Fully_Declared (P_Type, P);
1300          end if;
1301       end Check_Not_Incomplete_Type;
1302
1303       ----------------------------
1304       -- Check_Object_Reference --
1305       ----------------------------
1306
1307       procedure Check_Object_Reference (P : Node_Id) is
1308          Rtyp : Entity_Id;
1309
1310       begin
1311          --  If we need an object, and we have a prefix that is the name of
1312          --  a function entity, convert it into a function call.
1313
1314          if Is_Entity_Name (P)
1315            and then Ekind (Entity (P)) = E_Function
1316          then
1317             Rtyp := Etype (Entity (P));
1318
1319             Rewrite (P,
1320               Make_Function_Call (Sloc (P),
1321                 Name => Relocate_Node (P)));
1322
1323             Analyze_And_Resolve (P, Rtyp);
1324
1325          --  Otherwise we must have an object reference
1326
1327          elsif not Is_Object_Reference (P) then
1328             Error_Attr_P ("prefix of % attribute must be object");
1329          end if;
1330       end Check_Object_Reference;
1331
1332       ------------------------
1333       -- Check_Program_Unit --
1334       ------------------------
1335
1336       procedure Check_Program_Unit is
1337       begin
1338          if Is_Entity_Name (P) then
1339             declare
1340                K : constant Entity_Kind := Ekind (Entity (P));
1341                T : constant Entity_Id   := Etype (Entity (P));
1342
1343             begin
1344                if K in Subprogram_Kind
1345                  or else K in Task_Kind
1346                  or else K in Protected_Kind
1347                  or else K = E_Package
1348                  or else K in Generic_Unit_Kind
1349                  or else (K = E_Variable
1350                             and then
1351                               (Is_Task_Type (T)
1352                                  or else
1353                                Is_Protected_Type (T)))
1354                then
1355                   return;
1356                end if;
1357             end;
1358          end if;
1359
1360          Error_Attr_P ("prefix of % attribute must be program unit");
1361       end Check_Program_Unit;
1362
1363       ---------------------
1364       -- Check_Real_Type --
1365       ---------------------
1366
1367       procedure Check_Real_Type is
1368       begin
1369          Check_Type;
1370
1371          if not Is_Real_Type (P_Type) then
1372             Error_Attr_P ("prefix of % attribute must be real type");
1373          end if;
1374       end Check_Real_Type;
1375
1376       -----------------------
1377       -- Check_Scalar_Type --
1378       -----------------------
1379
1380       procedure Check_Scalar_Type is
1381       begin
1382          Check_Type;
1383
1384          if not Is_Scalar_Type (P_Type) then
1385             Error_Attr_P ("prefix of % attribute must be scalar type");
1386          end if;
1387       end Check_Scalar_Type;
1388
1389       ---------------------------
1390       -- Check_Standard_Prefix --
1391       ---------------------------
1392
1393       procedure Check_Standard_Prefix is
1394       begin
1395          Check_E0;
1396
1397          if Nkind (P) /= N_Identifier
1398            or else Chars (P) /= Name_Standard
1399          then
1400             Error_Attr ("only allowed prefix for % attribute is Standard", P);
1401          end if;
1402
1403       end Check_Standard_Prefix;
1404
1405       ----------------------------
1406       -- Check_Stream_Attribute --
1407       ----------------------------
1408
1409       procedure Check_Stream_Attribute (Nam : TSS_Name_Type) is
1410          Etyp : Entity_Id;
1411          Btyp : Entity_Id;
1412
1413       begin
1414          Validate_Non_Static_Attribute_Function_Call;
1415
1416          --  With the exception of 'Input, Stream attributes are procedures,
1417          --  and can only appear at the position of procedure calls. We check
1418          --  for this here, before they are rewritten, to give a more precise
1419          --  diagnostic.
1420
1421          if Nam = TSS_Stream_Input then
1422             null;
1423
1424          elsif Is_List_Member (N)
1425            and then Nkind (Parent (N)) /= N_Procedure_Call_Statement
1426            and then Nkind (Parent (N)) /= N_Aggregate
1427          then
1428             null;
1429
1430          else
1431             Error_Attr
1432               ("invalid context for attribute%, which is a procedure", N);
1433          end if;
1434
1435          Check_Type;
1436          Btyp := Implementation_Base_Type (P_Type);
1437
1438          --  Stream attributes not allowed on limited types unless the
1439          --  attribute reference was generated by the expander (in which
1440          --  case the underlying type will be used, as described in Sinfo),
1441          --  or the attribute was specified explicitly for the type itself
1442          --  or one of its ancestors (taking visibility rules into account if
1443          --  in Ada 2005 mode), or a pragma Stream_Convert applies to Btyp
1444          --  (with no visibility restriction).
1445
1446          if Comes_From_Source (N)
1447            and then not Stream_Attribute_Available (P_Type, Nam)
1448            and then not Has_Rep_Pragma (Btyp, Name_Stream_Convert)
1449          then
1450             Error_Msg_Name_1 := Aname;
1451
1452             if Is_Limited_Type (P_Type) then
1453                Error_Msg_NE
1454                  ("limited type& has no% attribute", P, P_Type);
1455                Explain_Limited_Type (P_Type, P);
1456             else
1457                Error_Msg_NE
1458                  ("attribute% for type& is not available", P, P_Type);
1459             end if;
1460          end if;
1461
1462          --  Check for violation of restriction No_Stream_Attributes
1463
1464          if Is_RTE (P_Type, RE_Exception_Id)
1465               or else
1466             Is_RTE (P_Type, RE_Exception_Occurrence)
1467          then
1468             Check_Restriction (No_Exception_Registration, P);
1469          end if;
1470
1471          --  Here we must check that the first argument is an access type
1472          --  that is compatible with Ada.Streams.Root_Stream_Type'Class.
1473
1474          Analyze_And_Resolve (E1);
1475          Etyp := Etype (E1);
1476
1477          --  Note: the double call to Root_Type here is needed because the
1478          --  root type of a class-wide type is the corresponding type (e.g.
1479          --  X for X'Class, and we really want to go to the root.)
1480
1481          if not Is_Access_Type (Etyp)
1482            or else Root_Type (Root_Type (Designated_Type (Etyp))) /=
1483                      RTE (RE_Root_Stream_Type)
1484          then
1485             Error_Attr
1486               ("expected access to Ada.Streams.Root_Stream_Type''Class", E1);
1487          end if;
1488
1489          --  Check that the second argument is of the right type if there is
1490          --  one (the Input attribute has only one argument so this is skipped)
1491
1492          if Present (E2) then
1493             Analyze (E2);
1494
1495             if Nam = TSS_Stream_Read
1496               and then not Is_OK_Variable_For_Out_Formal (E2)
1497             then
1498                Error_Attr
1499                  ("second argument of % attribute must be a variable", E2);
1500             end if;
1501
1502             Resolve (E2, P_Type);
1503          end if;
1504       end Check_Stream_Attribute;
1505
1506       -----------------------
1507       -- Check_Task_Prefix --
1508       -----------------------
1509
1510       procedure Check_Task_Prefix is
1511       begin
1512          Analyze (P);
1513
1514          --  Ada 2005 (AI-345): Attribute 'Terminated can be applied to
1515          --  task interface class-wide types.
1516
1517          if Is_Task_Type (Etype (P))
1518            or else (Is_Access_Type (Etype (P))
1519                       and then Is_Task_Type (Designated_Type (Etype (P))))
1520            or else (Ada_Version >= Ada_05
1521                       and then Ekind (Etype (P)) = E_Class_Wide_Type
1522                       and then Is_Interface (Etype (P))
1523                       and then Is_Task_Interface (Etype (P)))
1524          then
1525             Resolve (P);
1526
1527          else
1528             if Ada_Version >= Ada_05 then
1529                Error_Attr_P
1530                  ("prefix of % attribute must be a task or a task " &
1531                   "interface class-wide object");
1532
1533             else
1534                Error_Attr_P ("prefix of % attribute must be a task");
1535             end if;
1536          end if;
1537       end Check_Task_Prefix;
1538
1539       ----------------
1540       -- Check_Type --
1541       ----------------
1542
1543       --  The possibilities are an entity name denoting a type, or an
1544       --  attribute reference that denotes a type (Base or Class). If
1545       --  the type is incomplete, replace it with its full view.
1546
1547       procedure Check_Type is
1548       begin
1549          if not Is_Entity_Name (P)
1550            or else not Is_Type (Entity (P))
1551          then
1552             Error_Attr_P ("prefix of % attribute must be a type");
1553
1554          elsif Ekind (Entity (P)) = E_Incomplete_Type
1555             and then Present (Full_View (Entity (P)))
1556          then
1557             P_Type := Full_View (Entity (P));
1558             Set_Entity (P, P_Type);
1559          end if;
1560       end Check_Type;
1561
1562       ---------------------
1563       -- Check_Unit_Name --
1564       ---------------------
1565
1566       procedure Check_Unit_Name (Nod : Node_Id) is
1567       begin
1568          if Nkind (Nod) = N_Identifier then
1569             return;
1570
1571          elsif Nkind (Nod) = N_Selected_Component then
1572             Check_Unit_Name (Prefix (Nod));
1573
1574             if Nkind (Selector_Name (Nod)) = N_Identifier then
1575                return;
1576             end if;
1577          end if;
1578
1579          Error_Attr ("argument for % attribute must be unit name", P);
1580       end Check_Unit_Name;
1581
1582       ----------------
1583       -- Error_Attr --
1584       ----------------
1585
1586       procedure Error_Attr is
1587       begin
1588          Set_Etype (N, Any_Type);
1589          Set_Entity (N, Any_Type);
1590          raise Bad_Attribute;
1591       end Error_Attr;
1592
1593       procedure Error_Attr (Msg : String; Error_Node : Node_Id) is
1594       begin
1595          Error_Msg_Name_1 := Aname;
1596          Error_Msg_N (Msg, Error_Node);
1597          Error_Attr;
1598       end Error_Attr;
1599
1600       ------------------
1601       -- Error_Attr_P --
1602       ------------------
1603
1604       procedure Error_Attr_P (Msg : String) is
1605       begin
1606          Error_Msg_Name_1 := Aname;
1607          Error_Msg_F (Msg, P);
1608          Error_Attr;
1609       end Error_Attr_P;
1610
1611       ----------------------------
1612       -- Legal_Formal_Attribute --
1613       ----------------------------
1614
1615       procedure Legal_Formal_Attribute is
1616       begin
1617          Check_E0;
1618
1619          if not Is_Entity_Name (P)
1620            or else not Is_Type (Entity (P))
1621          then
1622             Error_Attr_P ("prefix of % attribute must be generic type");
1623
1624          elsif Is_Generic_Actual_Type (Entity (P))
1625            or else In_Instance
1626            or else In_Inlined_Body
1627          then
1628             null;
1629
1630          elsif Is_Generic_Type (Entity (P)) then
1631             if not Is_Indefinite_Subtype (Entity (P)) then
1632                Error_Attr_P
1633                  ("prefix of % attribute must be indefinite generic type");
1634             end if;
1635
1636          else
1637             Error_Attr_P
1638               ("prefix of % attribute must be indefinite generic type");
1639          end if;
1640
1641          Set_Etype (N, Standard_Boolean);
1642       end Legal_Formal_Attribute;
1643
1644       ------------------------
1645       -- Standard_Attribute --
1646       ------------------------
1647
1648       procedure Standard_Attribute (Val : Int) is
1649       begin
1650          Check_Standard_Prefix;
1651          Rewrite (N, Make_Integer_Literal (Loc, Val));
1652          Analyze (N);
1653       end Standard_Attribute;
1654
1655       -------------------------
1656       -- Unexpected Argument --
1657       -------------------------
1658
1659       procedure Unexpected_Argument (En : Node_Id) is
1660       begin
1661          Error_Attr ("unexpected argument for % attribute", En);
1662       end Unexpected_Argument;
1663
1664       -------------------------------------------------
1665       -- Validate_Non_Static_Attribute_Function_Call --
1666       -------------------------------------------------
1667
1668       --  This function should be moved to Sem_Dist ???
1669
1670       procedure Validate_Non_Static_Attribute_Function_Call is
1671       begin
1672          if In_Preelaborated_Unit
1673            and then not In_Subprogram_Or_Concurrent_Unit
1674          then
1675             Flag_Non_Static_Expr
1676               ("non-static function call in preelaborated unit!", N);
1677          end if;
1678       end Validate_Non_Static_Attribute_Function_Call;
1679
1680    -----------------------------------------------
1681    -- Start of Processing for Analyze_Attribute --
1682    -----------------------------------------------
1683
1684    begin
1685       --  Immediate return if unrecognized attribute (already diagnosed
1686       --  by parser, so there is nothing more that we need to do)
1687
1688       if not Is_Attribute_Name (Aname) then
1689          raise Bad_Attribute;
1690       end if;
1691
1692       --  Deal with Ada 83 issues
1693
1694       if Comes_From_Source (N) then
1695          if not Attribute_83 (Attr_Id) then
1696             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
1697                Error_Msg_Name_1 := Aname;
1698                Error_Msg_N ("(Ada 83) attribute% is not standard?", N);
1699             end if;
1700
1701             if Attribute_Impl_Def (Attr_Id) then
1702                Check_Restriction (No_Implementation_Attributes, N);
1703             end if;
1704          end if;
1705       end if;
1706
1707       --  Deal with Ada 2005 issues
1708
1709       if Attribute_05 (Attr_Id) and then Ada_Version <= Ada_95 then
1710          Check_Restriction (No_Implementation_Attributes, N);
1711       end if;
1712
1713       --   Remote access to subprogram type access attribute reference needs
1714       --   unanalyzed copy for tree transformation. The analyzed copy is used
1715       --   for its semantic information (whether prefix is a remote subprogram
1716       --   name), the unanalyzed copy is used to construct new subtree rooted
1717       --   with N_Aggregate which represents a fat pointer aggregate.
1718
1719       if Aname = Name_Access then
1720          Discard_Node (Copy_Separate_Tree (N));
1721       end if;
1722
1723       --  Analyze prefix and exit if error in analysis. If the prefix is an
1724       --  incomplete type, use full view if available. Note that there are
1725       --  some attributes for which we do not analyze the prefix, since the
1726       --  prefix is not a normal name.
1727
1728       if Aname /= Name_Elab_Body
1729            and then
1730          Aname /= Name_Elab_Spec
1731            and then
1732          Aname /= Name_UET_Address
1733            and then
1734          Aname /= Name_Enabled
1735       then
1736          Analyze (P);
1737          P_Type := Etype (P);
1738
1739          if Is_Entity_Name (P)
1740            and then Present (Entity (P))
1741            and then Is_Type (Entity (P))
1742          then
1743             if Ekind (Entity (P)) = E_Incomplete_Type then
1744                P_Type := Get_Full_View (P_Type);
1745                Set_Entity (P, P_Type);
1746                Set_Etype  (P, P_Type);
1747
1748             elsif Entity (P) = Current_Scope
1749               and then Is_Record_Type (Entity (P))
1750             then
1751                --  Use of current instance within the type. Verify that if the
1752                --  attribute appears within a constraint, it  yields an access
1753                --  type, other uses are illegal.
1754
1755                declare
1756                   Par : Node_Id;
1757
1758                begin
1759                   Par := Parent (N);
1760                   while Present (Par)
1761                     and then Nkind (Parent (Par)) /= N_Component_Definition
1762                   loop
1763                      Par := Parent (Par);
1764                   end loop;
1765
1766                   if Present (Par)
1767                     and then Nkind (Par) = N_Subtype_Indication
1768                   then
1769                      if Attr_Id /= Attribute_Access
1770                        and then Attr_Id /= Attribute_Unchecked_Access
1771                        and then Attr_Id /= Attribute_Unrestricted_Access
1772                      then
1773                         Error_Msg_N
1774                           ("in a constraint the current instance can only"
1775                              & " be used with an access attribute", N);
1776                      end if;
1777                   end if;
1778                end;
1779             end if;
1780          end if;
1781
1782          if P_Type = Any_Type then
1783             raise Bad_Attribute;
1784          end if;
1785
1786          P_Base_Type := Base_Type (P_Type);
1787       end if;
1788
1789       --  Analyze expressions that may be present, exiting if an error occurs
1790
1791       if No (Exprs) then
1792          E1 := Empty;
1793          E2 := Empty;
1794
1795       else
1796          E1 := First (Exprs);
1797          Analyze (E1);
1798
1799          --  Check for missing/bad expression (result of previous error)
1800
1801          if No (E1) or else Etype (E1) = Any_Type then
1802             raise Bad_Attribute;
1803          end if;
1804
1805          E2 := Next (E1);
1806
1807          if Present (E2) then
1808             Analyze (E2);
1809
1810             if Etype (E2) = Any_Type then
1811                raise Bad_Attribute;
1812             end if;
1813
1814             if Present (Next (E2)) then
1815                Unexpected_Argument (Next (E2));
1816             end if;
1817          end if;
1818       end if;
1819
1820       --  Ada 2005 (AI-345): Ensure that the compiler gives exactly the current
1821       --  output compiling in Ada 95 mode for the case of ambiguous prefixes.
1822
1823       if Ada_Version < Ada_05
1824         and then Is_Overloaded (P)
1825         and then Aname /= Name_Access
1826         and then Aname /= Name_Address
1827         and then Aname /= Name_Code_Address
1828         and then Aname /= Name_Count
1829         and then Aname /= Name_Unchecked_Access
1830       then
1831          Error_Attr ("ambiguous prefix for % attribute", P);
1832
1833       elsif Ada_Version >= Ada_05
1834         and then Is_Overloaded (P)
1835         and then Aname /= Name_Access
1836         and then Aname /= Name_Address
1837         and then Aname /= Name_Code_Address
1838         and then Aname /= Name_Unchecked_Access
1839       then
1840          --  Ada 2005 (AI-345): Since protected and task types have primitive
1841          --  entry wrappers, the attributes Count, Caller and AST_Entry require
1842          --  a context check
1843
1844          if Ada_Version >= Ada_05
1845            and then (Aname = Name_Count
1846                       or else Aname = Name_Caller
1847                       or else Aname = Name_AST_Entry)
1848          then
1849             declare
1850                Count : Natural := 0;
1851                I     : Interp_Index;
1852                It    : Interp;
1853
1854             begin
1855                Get_First_Interp (P, I, It);
1856                while Present (It.Nam) loop
1857                   if Comes_From_Source (It.Nam) then
1858                      Count := Count + 1;
1859                   else
1860                      Remove_Interp (I);
1861                   end if;
1862
1863                   Get_Next_Interp (I, It);
1864                end loop;
1865
1866                if Count > 1 then
1867                   Error_Attr ("ambiguous prefix for % attribute", P);
1868                else
1869                   Set_Is_Overloaded (P, False);
1870                end if;
1871             end;
1872
1873          else
1874             Error_Attr ("ambiguous prefix for % attribute", P);
1875          end if;
1876       end if;
1877
1878       --  Remaining processing depends on attribute
1879
1880       case Attr_Id is
1881
1882       ------------------
1883       -- Abort_Signal --
1884       ------------------
1885
1886       when Attribute_Abort_Signal =>
1887          Check_Standard_Prefix;
1888          Rewrite (N,
1889            New_Reference_To (Stand.Abort_Signal, Loc));
1890          Analyze (N);
1891
1892       ------------
1893       -- Access --
1894       ------------
1895
1896       when Attribute_Access =>
1897          Analyze_Access_Attribute;
1898
1899       -------------
1900       -- Address --
1901       -------------
1902
1903       when Attribute_Address =>
1904          Check_E0;
1905
1906          --  Check for some junk cases, where we have to allow the address
1907          --  attribute but it does not make much sense, so at least for now
1908          --  just replace with Null_Address.
1909
1910          --  We also do this if the prefix is a reference to the AST_Entry
1911          --  attribute. If expansion is active, the attribute will be
1912          --  replaced by a function call, and address will work fine and
1913          --  get the proper value, but if expansion is not active, then
1914          --  the check here allows proper semantic analysis of the reference.
1915
1916          --  An Address attribute created by expansion is legal even when it
1917          --  applies to other entity-denoting expressions.
1918
1919          if Is_Entity_Name (P) then
1920             declare
1921                Ent : constant Entity_Id := Entity (P);
1922
1923             begin
1924                if Is_Subprogram (Ent) then
1925                   if not Is_Library_Level_Entity (Ent) then
1926                      Check_Restriction (No_Implicit_Dynamic_Code, P);
1927                   end if;
1928
1929                   Set_Address_Taken (Ent);
1930                   Kill_Current_Values (Ent);
1931
1932                   --  An Address attribute is accepted when generated by the
1933                   --  compiler for dispatching operation, and an error is
1934                   --  issued once the subprogram is frozen (to avoid confusing
1935                   --  errors about implicit uses of Address in the dispatch
1936                   --  table initialization).
1937
1938                   if Is_Always_Inlined (Entity (P))
1939                     and then Comes_From_Source (P)
1940                   then
1941                      Error_Attr_P
1942                        ("prefix of % attribute cannot be Inline_Always" &
1943                         " subprogram");
1944                   end if;
1945
1946                elsif Is_Object (Ent)
1947                  or else Ekind (Ent) = E_Label
1948                then
1949                   Set_Address_Taken (Ent);
1950
1951                --  If we have an address of an object, and the attribute
1952                --  comes from source, then set the object as potentially
1953                --  source modified. We do this because the resulting address
1954                --  can potentially be used to modify the variable and we
1955                --  might not detect this, leading to some junk warnings.
1956
1957                   Set_Never_Set_In_Source (Ent, False);
1958
1959                elsif (Is_Concurrent_Type (Etype (Ent))
1960                        and then Etype (Ent) = Base_Type (Ent))
1961                  or else Ekind (Ent) = E_Package
1962                  or else Is_Generic_Unit (Ent)
1963                then
1964                   Rewrite (N,
1965                     New_Occurrence_Of (RTE (RE_Null_Address), Sloc (N)));
1966
1967                else
1968                   Error_Attr ("invalid prefix for % attribute", P);
1969                end if;
1970             end;
1971
1972          elsif Nkind (P) = N_Attribute_Reference
1973            and then Attribute_Name (P) = Name_AST_Entry
1974          then
1975             Rewrite (N,
1976               New_Occurrence_Of (RTE (RE_Null_Address), Sloc (N)));
1977
1978          elsif Is_Object_Reference (P) then
1979             null;
1980
1981          elsif Nkind (P) = N_Selected_Component
1982            and then Is_Subprogram (Entity (Selector_Name (P)))
1983          then
1984             null;
1985
1986          --  What exactly are we allowing here ??? and is this properly
1987          --  documented in the sinfo documentation for this node ???
1988
1989          elsif not Comes_From_Source (N) then
1990             null;
1991
1992          else
1993             Error_Attr ("invalid prefix for % attribute", P);
1994          end if;
1995
1996          Set_Etype (N, RTE (RE_Address));
1997
1998       ------------------
1999       -- Address_Size --
2000       ------------------
2001
2002       when Attribute_Address_Size =>
2003          Standard_Attribute (System_Address_Size);
2004
2005       --------------
2006       -- Adjacent --
2007       --------------
2008
2009       when Attribute_Adjacent =>
2010          Check_Floating_Point_Type_2;
2011          Set_Etype (N, P_Base_Type);
2012          Resolve (E1, P_Base_Type);
2013          Resolve (E2, P_Base_Type);
2014
2015       ---------
2016       -- Aft --
2017       ---------
2018
2019       when Attribute_Aft =>
2020          Check_Fixed_Point_Type_0;
2021          Set_Etype (N, Universal_Integer);
2022
2023       ---------------
2024       -- Alignment --
2025       ---------------
2026
2027       when Attribute_Alignment =>
2028
2029          --  Don't we need more checking here, cf Size ???
2030
2031          Check_E0;
2032          Check_Not_Incomplete_Type;
2033          Set_Etype (N, Universal_Integer);
2034
2035       ---------------
2036       -- Asm_Input --
2037       ---------------
2038
2039       when Attribute_Asm_Input =>
2040          Check_Asm_Attribute;
2041          Set_Etype (N, RTE (RE_Asm_Input_Operand));
2042
2043       ----------------
2044       -- Asm_Output --
2045       ----------------
2046
2047       when Attribute_Asm_Output =>
2048          Check_Asm_Attribute;
2049
2050          if Etype (E2) = Any_Type then
2051             return;
2052
2053          elsif Aname = Name_Asm_Output then
2054             if not Is_Variable (E2) then
2055                Error_Attr
2056                  ("second argument for Asm_Output is not variable", E2);
2057             end if;
2058          end if;
2059
2060          Note_Possible_Modification (E2);
2061          Set_Etype (N, RTE (RE_Asm_Output_Operand));
2062
2063       ---------------
2064       -- AST_Entry --
2065       ---------------
2066
2067       when Attribute_AST_Entry => AST_Entry : declare
2068          Ent  : Entity_Id;
2069          Pref : Node_Id;
2070          Ptyp : Entity_Id;
2071
2072          Indexed : Boolean;
2073          --  Indicates if entry family index is present. Note the coding
2074          --  here handles the entry family case, but in fact it cannot be
2075          --  executed currently, because pragma AST_Entry does not permit
2076          --  the specification of an entry family.
2077
2078          procedure Bad_AST_Entry;
2079          --  Signal a bad AST_Entry pragma
2080
2081          function OK_Entry (E : Entity_Id) return Boolean;
2082          --  Checks that E is of an appropriate entity kind for an entry
2083          --  (i.e. E_Entry if Index is False, or E_Entry_Family if Index
2084          --  is set True for the entry family case). In the True case,
2085          --  makes sure that Is_AST_Entry is set on the entry.
2086
2087          procedure Bad_AST_Entry is
2088          begin
2089             Error_Attr_P ("prefix for % attribute must be task entry");
2090          end Bad_AST_Entry;
2091
2092          function OK_Entry (E : Entity_Id) return Boolean is
2093             Result : Boolean;
2094
2095          begin
2096             if Indexed then
2097                Result := (Ekind (E) = E_Entry_Family);
2098             else
2099                Result := (Ekind (E) = E_Entry);
2100             end if;
2101
2102             if Result then
2103                if not Is_AST_Entry (E) then
2104                   Error_Msg_Name_2 := Aname;
2105                   Error_Attr ("% attribute requires previous % pragma", P);
2106                end if;
2107             end if;
2108
2109             return Result;
2110          end OK_Entry;
2111
2112       --  Start of processing for AST_Entry
2113
2114       begin
2115          Check_VMS (N);
2116          Check_E0;
2117
2118          --  Deal with entry family case
2119
2120          if Nkind (P) = N_Indexed_Component then
2121             Pref := Prefix (P);
2122             Indexed := True;
2123          else
2124             Pref := P;
2125             Indexed := False;
2126          end if;
2127
2128          Ptyp := Etype (Pref);
2129
2130          if Ptyp = Any_Type or else Error_Posted (Pref) then
2131             return;
2132          end if;
2133
2134          --  If the prefix is a selected component whose prefix is of an
2135          --  access type, then introduce an explicit dereference.
2136          --  ??? Could we reuse Check_Dereference here?
2137
2138          if Nkind (Pref) = N_Selected_Component
2139            and then Is_Access_Type (Ptyp)
2140          then
2141             Rewrite (Pref,
2142               Make_Explicit_Dereference (Sloc (Pref),
2143                 Relocate_Node (Pref)));
2144             Analyze_And_Resolve (Pref, Designated_Type (Ptyp));
2145          end if;
2146
2147          --  Prefix can be of the form a.b, where a is a task object
2148          --  and b is one of the entries of the corresponding task type.
2149
2150          if Nkind (Pref) = N_Selected_Component
2151            and then OK_Entry (Entity (Selector_Name (Pref)))
2152            and then Is_Object_Reference (Prefix (Pref))
2153            and then Is_Task_Type (Etype (Prefix (Pref)))
2154          then
2155             null;
2156
2157          --  Otherwise the prefix must be an entry of a containing task,
2158          --  or of a variable of the enclosing task type.
2159
2160          else
2161             if Nkind (Pref) = N_Identifier
2162               or else Nkind (Pref) = N_Expanded_Name
2163             then
2164                Ent := Entity (Pref);
2165
2166                if not OK_Entry (Ent)
2167                  or else not In_Open_Scopes (Scope (Ent))
2168                then
2169                   Bad_AST_Entry;
2170                end if;
2171
2172             else
2173                Bad_AST_Entry;
2174             end if;
2175          end if;
2176
2177          Set_Etype (N, RTE (RE_AST_Handler));
2178       end AST_Entry;
2179
2180       ----------
2181       -- Base --
2182       ----------
2183
2184       --  Note: when the base attribute appears in the context of a subtype
2185       --  mark, the analysis is done by Sem_Ch8.Find_Type, rather than by
2186       --  the following circuit.
2187
2188       when Attribute_Base => Base : declare
2189          Typ : Entity_Id;
2190
2191       begin
2192          Check_Either_E0_Or_E1;
2193          Find_Type (P);
2194          Typ := Entity (P);
2195
2196          if Ada_Version >= Ada_95
2197            and then not Is_Scalar_Type (Typ)
2198            and then not Is_Generic_Type (Typ)
2199          then
2200             Error_Attr_P ("prefix of Base attribute must be scalar type");
2201
2202          elsif Sloc (Typ) = Standard_Location
2203            and then Base_Type (Typ) = Typ
2204            and then Warn_On_Redundant_Constructs
2205          then
2206                Error_Msg_NE
2207                  ("?redudant attribute, & is its own base type", N, Typ);
2208          end if;
2209
2210          Set_Etype (N, Base_Type (Entity (P)));
2211
2212          --  If we have an expression present, then really this is a conversion
2213          --  and the tree must be reformed. Note that this is one of the cases
2214          --  in which we do a replace rather than a rewrite, because the
2215          --  original tree is junk.
2216
2217          if Present (E1) then
2218             Replace (N,
2219               Make_Type_Conversion (Loc,
2220                 Subtype_Mark =>
2221                   Make_Attribute_Reference (Loc,
2222                     Prefix => Prefix (N),
2223                     Attribute_Name => Name_Base),
2224                 Expression => Relocate_Node (E1)));
2225
2226             --  E1 may be overloaded, and its interpretations preserved
2227
2228             Save_Interps (E1, Expression (N));
2229             Analyze (N);
2230
2231          --  For other cases, set the proper type as the entity of the
2232          --  attribute reference, and then rewrite the node to be an
2233          --  occurrence of the referenced base type. This way, no one
2234          --  else in the compiler has to worry about the base attribute.
2235
2236          else
2237             Set_Entity (N, Base_Type (Entity (P)));
2238             Rewrite (N,
2239               New_Reference_To (Entity (N), Loc));
2240             Analyze (N);
2241          end if;
2242       end Base;
2243
2244       ---------
2245       -- Bit --
2246       ---------
2247
2248       when Attribute_Bit => Bit :
2249       begin
2250          Check_E0;
2251
2252          if not Is_Object_Reference (P) then
2253             Error_Attr_P ("prefix for % attribute must be object");
2254
2255          --  What about the access object cases ???
2256
2257          else
2258             null;
2259          end if;
2260
2261          Set_Etype (N, Universal_Integer);
2262       end Bit;
2263
2264       ---------------
2265       -- Bit_Order --
2266       ---------------
2267
2268       when Attribute_Bit_Order => Bit_Order :
2269       begin
2270          Check_E0;
2271          Check_Type;
2272
2273          if not Is_Record_Type (P_Type) then
2274             Error_Attr_P ("prefix of % attribute must be record type");
2275          end if;
2276
2277          if Bytes_Big_Endian xor Reverse_Bit_Order (P_Type) then
2278             Rewrite (N,
2279               New_Occurrence_Of (RTE (RE_High_Order_First), Loc));
2280          else
2281             Rewrite (N,
2282               New_Occurrence_Of (RTE (RE_Low_Order_First), Loc));
2283          end if;
2284
2285          Set_Etype (N, RTE (RE_Bit_Order));
2286          Resolve (N);
2287
2288          --  Reset incorrect indication of staticness
2289
2290          Set_Is_Static_Expression (N, False);
2291       end Bit_Order;
2292
2293       ------------------
2294       -- Bit_Position --
2295       ------------------
2296
2297       --  Note: in generated code, we can have a Bit_Position attribute
2298       --  applied to a (naked) record component (i.e. the prefix is an
2299       --  identifier that references an E_Component or E_Discriminant
2300       --  entity directly, and this is interpreted as expected by Gigi.
2301       --  The following code will not tolerate such usage, but when the
2302       --  expander creates this special case, it marks it as analyzed
2303       --  immediately and sets an appropriate type.
2304
2305       when Attribute_Bit_Position =>
2306          if Comes_From_Source (N) then
2307             Check_Component;
2308          end if;
2309
2310          Set_Etype (N, Universal_Integer);
2311
2312       ------------------
2313       -- Body_Version --
2314       ------------------
2315
2316       when Attribute_Body_Version =>
2317          Check_E0;
2318          Check_Program_Unit;
2319          Set_Etype (N, RTE (RE_Version_String));
2320
2321       --------------
2322       -- Callable --
2323       --------------
2324
2325       when Attribute_Callable =>
2326          Check_E0;
2327          Set_Etype (N, Standard_Boolean);
2328          Check_Task_Prefix;
2329
2330       ------------
2331       -- Caller --
2332       ------------
2333
2334       when Attribute_Caller => Caller : declare
2335          Ent        : Entity_Id;
2336          S          : Entity_Id;
2337
2338       begin
2339          Check_E0;
2340
2341          if Nkind (P) = N_Identifier
2342            or else Nkind (P) = N_Expanded_Name
2343          then
2344             Ent := Entity (P);
2345
2346             if not Is_Entry (Ent) then
2347                Error_Attr ("invalid entry name", N);
2348             end if;
2349
2350          else
2351             Error_Attr ("invalid entry name", N);
2352             return;
2353          end if;
2354
2355          for J in reverse 0 .. Scope_Stack.Last loop
2356             S := Scope_Stack.Table (J).Entity;
2357
2358             if S = Scope (Ent) then
2359                Error_Attr ("Caller must appear in matching accept or body", N);
2360             elsif S = Ent then
2361                exit;
2362             end if;
2363          end loop;
2364
2365          Set_Etype (N, RTE (RO_AT_Task_Id));
2366       end Caller;
2367
2368       -------------
2369       -- Ceiling --
2370       -------------
2371
2372       when Attribute_Ceiling =>
2373          Check_Floating_Point_Type_1;
2374          Set_Etype (N, P_Base_Type);
2375          Resolve (E1, P_Base_Type);
2376
2377       -----------
2378       -- Class --
2379       -----------
2380
2381       when Attribute_Class => Class : declare
2382          P : constant Entity_Id := Prefix (N);
2383
2384       begin
2385          Check_Restriction (No_Dispatch, N);
2386          Check_Either_E0_Or_E1;
2387
2388          --  If we have an expression present, then really this is a conversion
2389          --  and the tree must be reformed into a proper conversion. This is a
2390          --  Replace rather than a Rewrite, because the original tree is junk.
2391          --  If expression is overloaded, propagate interpretations to new one.
2392
2393          if Present (E1) then
2394             Replace (N,
2395               Make_Type_Conversion (Loc,
2396                 Subtype_Mark =>
2397                   Make_Attribute_Reference (Loc,
2398                     Prefix => P,
2399                     Attribute_Name => Name_Class),
2400                 Expression => Relocate_Node (E1)));
2401
2402             Save_Interps (E1, Expression (N));
2403
2404             --  Ada 2005 (AI-251): In case of abstract interfaces we have to
2405             --  analyze and resolve the type conversion to generate the code
2406             --  that displaces the reference to the base of the object.
2407
2408             if Is_Interface (Etype (P))
2409               or else Is_Interface (Etype (E1))
2410             then
2411                Analyze_And_Resolve (N, Etype (P));
2412
2413                --  However, the attribute is a name that occurs in a context
2414                --  that imposes its own type. Leave the result unanalyzed,
2415                --  so that type checking with the context type take place.
2416                --  on the new conversion node, otherwise Resolve is a noop.
2417
2418                Set_Analyzed (N, False);
2419
2420             else
2421                Analyze (N);
2422             end if;
2423
2424          --  Otherwise we just need to find the proper type
2425
2426          else
2427             Find_Type (N);
2428          end if;
2429       end Class;
2430
2431       ------------------
2432       -- Code_Address --
2433       ------------------
2434
2435       when Attribute_Code_Address =>
2436          Check_E0;
2437
2438          if Nkind (P) = N_Attribute_Reference
2439            and then (Attribute_Name (P) = Name_Elab_Body
2440                        or else
2441                      Attribute_Name (P) = Name_Elab_Spec)
2442          then
2443             null;
2444
2445          elsif not Is_Entity_Name (P)
2446            or else (Ekind (Entity (P)) /= E_Function
2447                       and then
2448                     Ekind (Entity (P)) /= E_Procedure)
2449          then
2450             Error_Attr ("invalid prefix for % attribute", P);
2451             Set_Address_Taken (Entity (P));
2452          end if;
2453
2454          Set_Etype (N, RTE (RE_Address));
2455
2456       --------------------
2457       -- Component_Size --
2458       --------------------
2459
2460       when Attribute_Component_Size =>
2461          Check_E0;
2462          Set_Etype (N, Universal_Integer);
2463
2464          --  Note: unlike other array attributes, unconstrained arrays are OK
2465
2466          if Is_Array_Type (P_Type) and then not Is_Constrained (P_Type) then
2467             null;
2468          else
2469             Check_Array_Type;
2470          end if;
2471
2472       -------------
2473       -- Compose --
2474       -------------
2475
2476       when Attribute_Compose =>
2477          Check_Floating_Point_Type_2;
2478          Set_Etype (N, P_Base_Type);
2479          Resolve (E1, P_Base_Type);
2480          Resolve (E2, Any_Integer);
2481
2482       -----------------
2483       -- Constrained --
2484       -----------------
2485
2486       when Attribute_Constrained =>
2487          Check_E0;
2488          Set_Etype (N, Standard_Boolean);
2489
2490          --  Case from RM J.4(2) of constrained applied to private type
2491
2492          if Is_Entity_Name (P) and then Is_Type (Entity (P)) then
2493             Check_Restriction (No_Obsolescent_Features, N);
2494
2495             if Warn_On_Obsolescent_Feature then
2496                Error_Msg_N
2497                  ("constrained for private type is an " &
2498                   "obsolescent feature (RM J.4)?", N);
2499             end if;
2500
2501             --  If we are within an instance, the attribute must be legal
2502             --  because it was valid in the generic unit. Ditto if this is
2503             --  an inlining of a function declared in an instance.
2504
2505             if In_Instance
2506               or else In_Inlined_Body
2507             then
2508                return;
2509
2510             --  For sure OK if we have a real private type itself, but must
2511             --  be completed, cannot apply Constrained to incomplete type.
2512
2513             elsif Is_Private_Type (Entity (P)) then
2514
2515                --  Note: this is one of the Annex J features that does not
2516                --  generate a warning from -gnatwj, since in fact it seems
2517                --  very useful, and is used in the GNAT runtime.
2518
2519                Check_Not_Incomplete_Type;
2520                return;
2521             end if;
2522
2523          --  Normal (non-obsolescent case) of application to object of
2524          --  a discriminated type.
2525
2526          else
2527             Check_Object_Reference (P);
2528
2529             --  If N does not come from source, then we allow the
2530             --  the attribute prefix to be of a private type whose
2531             --  full type has discriminants. This occurs in cases
2532             --  involving expanded calls to stream attributes.
2533
2534             if not Comes_From_Source (N) then
2535                P_Type := Underlying_Type (P_Type);
2536             end if;
2537
2538             --  Must have discriminants or be an access type designating
2539             --  a type with discriminants. If it is a classwide type is ???
2540             --  has unknown discriminants.
2541
2542             if Has_Discriminants (P_Type)
2543                or else Has_Unknown_Discriminants (P_Type)
2544                or else
2545                  (Is_Access_Type (P_Type)
2546                    and then Has_Discriminants (Designated_Type (P_Type)))
2547             then
2548                return;
2549
2550             --  Also allow an object of a generic type if extensions allowed
2551             --  and allow this for any type at all.
2552
2553             elsif (Is_Generic_Type (P_Type)
2554                      or else Is_Generic_Actual_Type (P_Type))
2555               and then Extensions_Allowed
2556             then
2557                return;
2558             end if;
2559          end if;
2560
2561          --  Fall through if bad prefix
2562
2563          Error_Attr_P
2564            ("prefix of % attribute must be object of discriminated type");
2565
2566       ---------------
2567       -- Copy_Sign --
2568       ---------------
2569
2570       when Attribute_Copy_Sign =>
2571          Check_Floating_Point_Type_2;
2572          Set_Etype (N, P_Base_Type);
2573          Resolve (E1, P_Base_Type);
2574          Resolve (E2, P_Base_Type);
2575
2576       -----------
2577       -- Count --
2578       -----------
2579
2580       when Attribute_Count => Count :
2581       declare
2582          Ent : Entity_Id;
2583          S   : Entity_Id;
2584          Tsk : Entity_Id;
2585
2586       begin
2587          Check_E0;
2588
2589          if Nkind (P) = N_Identifier
2590            or else Nkind (P) = N_Expanded_Name
2591          then
2592             Ent := Entity (P);
2593
2594             if Ekind (Ent) /= E_Entry then
2595                Error_Attr ("invalid entry name", N);
2596             end if;
2597
2598          elsif Nkind (P) = N_Indexed_Component then
2599             if not Is_Entity_Name (Prefix (P))
2600               or else  No (Entity (Prefix (P)))
2601               or else Ekind (Entity (Prefix (P))) /= E_Entry_Family
2602             then
2603                if Nkind (Prefix (P)) = N_Selected_Component
2604                  and then Present (Entity (Selector_Name (Prefix (P))))
2605                  and then Ekind (Entity (Selector_Name (Prefix (P)))) =
2606                                                              E_Entry_Family
2607                then
2608                   Error_Attr
2609                     ("attribute % must apply to entry of current task", P);
2610
2611                else
2612                   Error_Attr ("invalid entry family name", P);
2613                end if;
2614                return;
2615
2616             else
2617                Ent := Entity (Prefix (P));
2618             end if;
2619
2620          elsif Nkind (P) = N_Selected_Component
2621            and then Present (Entity (Selector_Name (P)))
2622            and then Ekind (Entity (Selector_Name (P))) = E_Entry
2623          then
2624             Error_Attr
2625               ("attribute % must apply to entry of current task", P);
2626
2627          else
2628             Error_Attr ("invalid entry name", N);
2629             return;
2630          end if;
2631
2632          for J in reverse 0 .. Scope_Stack.Last loop
2633             S := Scope_Stack.Table (J).Entity;
2634
2635             if S = Scope (Ent) then
2636                if Nkind (P) = N_Expanded_Name then
2637                   Tsk := Entity (Prefix (P));
2638
2639                   --  The prefix denotes either the task type, or else a
2640                   --  single task whose task type is being analyzed.
2641
2642                   if (Is_Type (Tsk)
2643                       and then Tsk = S)
2644
2645                     or else (not Is_Type (Tsk)
2646                       and then Etype (Tsk) = S
2647                       and then not (Comes_From_Source (S)))
2648                   then
2649                      null;
2650                   else
2651                      Error_Attr
2652                        ("Attribute % must apply to entry of current task", N);
2653                   end if;
2654                end if;
2655
2656                exit;
2657
2658             elsif Ekind (Scope (Ent)) in Task_Kind
2659               and then Ekind (S) /= E_Loop
2660               and then Ekind (S) /= E_Block
2661               and then Ekind (S) /= E_Entry
2662               and then Ekind (S) /= E_Entry_Family
2663             then
2664                Error_Attr ("Attribute % cannot appear in inner unit", N);
2665
2666             elsif Ekind (Scope (Ent)) = E_Protected_Type
2667               and then not Has_Completion (Scope (Ent))
2668             then
2669                Error_Attr ("attribute % can only be used inside body", N);
2670             end if;
2671          end loop;
2672
2673          if Is_Overloaded (P) then
2674             declare
2675                Index : Interp_Index;
2676                It    : Interp;
2677
2678             begin
2679                Get_First_Interp (P, Index, It);
2680
2681                while Present (It.Nam) loop
2682                   if It.Nam = Ent then
2683                      null;
2684
2685                   --  Ada 2005 (AI-345): Do not consider primitive entry
2686                   --  wrappers generated for task or protected types.
2687
2688                   elsif Ada_Version >= Ada_05
2689                     and then not Comes_From_Source (It.Nam)
2690                   then
2691                      null;
2692
2693                   else
2694                      Error_Attr ("ambiguous entry name", N);
2695                   end if;
2696
2697                   Get_Next_Interp (Index, It);
2698                end loop;
2699             end;
2700          end if;
2701
2702          Set_Etype (N, Universal_Integer);
2703       end Count;
2704
2705       -----------------------
2706       -- Default_Bit_Order --
2707       -----------------------
2708
2709       when Attribute_Default_Bit_Order => Default_Bit_Order :
2710       begin
2711          Check_Standard_Prefix;
2712          Check_E0;
2713
2714          if Bytes_Big_Endian then
2715             Rewrite (N,
2716               Make_Integer_Literal (Loc, False_Value));
2717          else
2718             Rewrite (N,
2719               Make_Integer_Literal (Loc, True_Value));
2720          end if;
2721
2722          Set_Etype (N, Universal_Integer);
2723          Set_Is_Static_Expression (N);
2724       end Default_Bit_Order;
2725
2726       --------------
2727       -- Definite --
2728       --------------
2729
2730       when Attribute_Definite =>
2731          Legal_Formal_Attribute;
2732
2733       -----------
2734       -- Delta --
2735       -----------
2736
2737       when Attribute_Delta =>
2738          Check_Fixed_Point_Type_0;
2739          Set_Etype (N, Universal_Real);
2740
2741       ------------
2742       -- Denorm --
2743       ------------
2744
2745       when Attribute_Denorm =>
2746          Check_Floating_Point_Type_0;
2747          Set_Etype (N, Standard_Boolean);
2748
2749       ------------
2750       -- Digits --
2751       ------------
2752
2753       when Attribute_Digits =>
2754          Check_E0;
2755          Check_Type;
2756
2757          if not Is_Floating_Point_Type (P_Type)
2758            and then not Is_Decimal_Fixed_Point_Type (P_Type)
2759          then
2760             Error_Attr_P
2761               ("prefix of % attribute must be float or decimal type");
2762          end if;
2763
2764          Set_Etype (N, Universal_Integer);
2765
2766       ---------------
2767       -- Elab_Body --
2768       ---------------
2769
2770       --  Also handles processing for Elab_Spec
2771
2772       when Attribute_Elab_Body | Attribute_Elab_Spec =>
2773          Check_E0;
2774          Check_Unit_Name (P);
2775          Set_Etype (N, Standard_Void_Type);
2776
2777          --  We have to manually call the expander in this case to get
2778          --  the necessary expansion (normally attributes that return
2779          --  entities are not expanded).
2780
2781          Expand (N);
2782
2783       ---------------
2784       -- Elab_Spec --
2785       ---------------
2786
2787       --  Shares processing with Elab_Body
2788
2789       ----------------
2790       -- Elaborated --
2791       ----------------
2792
2793       when Attribute_Elaborated =>
2794          Check_E0;
2795          Check_Library_Unit;
2796          Set_Etype (N, Standard_Boolean);
2797
2798       ----------
2799       -- Emax --
2800       ----------
2801
2802       when Attribute_Emax =>
2803          Check_Floating_Point_Type_0;
2804          Set_Etype (N, Universal_Integer);
2805
2806       -------------
2807       -- Enabled --
2808       -------------
2809
2810       when Attribute_Enabled =>
2811          Check_Either_E0_Or_E1;
2812
2813          if Present (E1) then
2814             if not Is_Entity_Name (E1) or else No (Entity (E1)) then
2815                Error_Msg_N ("entity name expected for Enabled attribute", E1);
2816                E1 := Empty;
2817             end if;
2818          end if;
2819
2820          if Nkind (P) /= N_Identifier then
2821             Error_Msg_N ("identifier expected (check name)", P);
2822
2823          elsif Get_Check_Id (Chars (P)) = No_Check_Id then
2824             Error_Msg_N ("& is not a recognized check name", P);
2825          end if;
2826
2827          Set_Etype (N, Standard_Boolean);
2828
2829       --------------
2830       -- Enum_Rep --
2831       --------------
2832
2833       when Attribute_Enum_Rep => Enum_Rep : declare
2834       begin
2835          if Present (E1) then
2836             Check_E1;
2837             Check_Discrete_Type;
2838             Resolve (E1, P_Base_Type);
2839
2840          else
2841             if not Is_Entity_Name (P)
2842               or else (not Is_Object (Entity (P))
2843                          and then
2844                        Ekind (Entity (P)) /= E_Enumeration_Literal)
2845             then
2846                Error_Attr_P
2847                  ("prefix of %attribute must be " &
2848                   "discrete type/object or enum literal");
2849             end if;
2850          end if;
2851
2852          Set_Etype (N, Universal_Integer);
2853       end Enum_Rep;
2854
2855       -------------
2856       -- Epsilon --
2857       -------------
2858
2859       when Attribute_Epsilon =>
2860          Check_Floating_Point_Type_0;
2861          Set_Etype (N, Universal_Real);
2862
2863       --------------
2864       -- Exponent --
2865       --------------
2866
2867       when Attribute_Exponent =>
2868          Check_Floating_Point_Type_1;
2869          Set_Etype (N, Universal_Integer);
2870          Resolve (E1, P_Base_Type);
2871
2872       ------------------
2873       -- External_Tag --
2874       ------------------
2875
2876       when Attribute_External_Tag =>
2877          Check_E0;
2878          Check_Type;
2879
2880          Set_Etype (N, Standard_String);
2881
2882          if not Is_Tagged_Type (P_Type) then
2883             Error_Attr_P ("prefix of % attribute must be tagged");
2884          end if;
2885
2886       -----------
2887       -- First --
2888       -----------
2889
2890       when Attribute_First =>
2891          Check_Array_Or_Scalar_Type;
2892
2893       ---------------
2894       -- First_Bit --
2895       ---------------
2896
2897       when Attribute_First_Bit =>
2898          Check_Component;
2899          Set_Etype (N, Universal_Integer);
2900
2901       -----------------
2902       -- Fixed_Value --
2903       -----------------
2904
2905       when Attribute_Fixed_Value =>
2906          Check_E1;
2907          Check_Fixed_Point_Type;
2908          Resolve (E1, Any_Integer);
2909          Set_Etype (N, P_Base_Type);
2910
2911       -----------
2912       -- Floor --
2913       -----------
2914
2915       when Attribute_Floor =>
2916          Check_Floating_Point_Type_1;
2917          Set_Etype (N, P_Base_Type);
2918          Resolve (E1, P_Base_Type);
2919
2920       ----------
2921       -- Fore --
2922       ----------
2923
2924       when Attribute_Fore =>
2925          Check_Fixed_Point_Type_0;
2926          Set_Etype (N, Universal_Integer);
2927
2928       --------------
2929       -- Fraction --
2930       --------------
2931
2932       when Attribute_Fraction =>
2933          Check_Floating_Point_Type_1;
2934          Set_Etype (N, P_Base_Type);
2935          Resolve (E1, P_Base_Type);
2936
2937       -----------------------
2938       -- Has_Access_Values --
2939       -----------------------
2940
2941       when Attribute_Has_Access_Values =>
2942          Check_Type;
2943          Check_E0;
2944          Set_Etype (N, Standard_Boolean);
2945
2946       -----------------------
2947       -- Has_Discriminants --
2948       -----------------------
2949
2950       when Attribute_Has_Discriminants =>
2951          Legal_Formal_Attribute;
2952
2953       --------------
2954       -- Identity --
2955       --------------
2956
2957       when Attribute_Identity =>
2958          Check_E0;
2959          Analyze (P);
2960
2961          if Etype (P) =  Standard_Exception_Type then
2962             Set_Etype (N, RTE (RE_Exception_Id));
2963
2964          --  Ada 2005 (AI-345): Attribute 'Identity may be applied to
2965          --  task interface class-wide types.
2966
2967          elsif Is_Task_Type (Etype (P))
2968            or else (Is_Access_Type (Etype (P))
2969                       and then Is_Task_Type (Designated_Type (Etype (P))))
2970            or else (Ada_Version >= Ada_05
2971                       and then Ekind (Etype (P)) = E_Class_Wide_Type
2972                       and then Is_Interface (Etype (P))
2973                       and then Is_Task_Interface (Etype (P)))
2974          then
2975             Resolve (P);
2976             Set_Etype (N, RTE (RO_AT_Task_Id));
2977
2978          else
2979             if Ada_Version >= Ada_05 then
2980                Error_Attr_P
2981                  ("prefix of % attribute must be an exception, a " &
2982                   "task or a task interface class-wide object");
2983             else
2984                Error_Attr_P
2985                  ("prefix of % attribute must be a task or an exception");
2986             end if;
2987          end if;
2988
2989       -----------
2990       -- Image --
2991       -----------
2992
2993       when Attribute_Image => Image :
2994       begin
2995          Set_Etype (N, Standard_String);
2996          Check_Scalar_Type;
2997
2998          if Is_Real_Type (P_Type) then
2999             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
3000                Error_Msg_Name_1 := Aname;
3001                Error_Msg_N
3002                  ("(Ada 83) % attribute not allowed for real types", N);
3003             end if;
3004          end if;
3005
3006          if Is_Enumeration_Type (P_Type) then
3007             Check_Restriction (No_Enumeration_Maps, N);
3008          end if;
3009
3010          Check_E1;
3011          Resolve (E1, P_Base_Type);
3012          Check_Enum_Image;
3013          Validate_Non_Static_Attribute_Function_Call;
3014       end Image;
3015
3016       ---------
3017       -- Img --
3018       ---------
3019
3020       when Attribute_Img => Img :
3021       begin
3022          Set_Etype (N, Standard_String);
3023
3024          if not Is_Scalar_Type (P_Type)
3025            or else (Is_Entity_Name (P) and then Is_Type (Entity (P)))
3026          then
3027             Error_Attr_P
3028               ("prefix of % attribute must be scalar object name");
3029          end if;
3030
3031          Check_Enum_Image;
3032       end Img;
3033
3034       -----------
3035       -- Input --
3036       -----------
3037
3038       when Attribute_Input =>
3039          Check_E1;
3040          Check_Stream_Attribute (TSS_Stream_Input);
3041          Set_Etype (N, P_Base_Type);
3042
3043       -------------------
3044       -- Integer_Value --
3045       -------------------
3046
3047       when Attribute_Integer_Value =>
3048          Check_E1;
3049          Check_Integer_Type;
3050          Resolve (E1, Any_Fixed);
3051          Set_Etype (N, P_Base_Type);
3052
3053       -----------
3054       -- Large --
3055       -----------
3056
3057       when Attribute_Large =>
3058          Check_E0;
3059          Check_Real_Type;
3060          Set_Etype (N, Universal_Real);
3061
3062       ----------
3063       -- Last --
3064       ----------
3065
3066       when Attribute_Last =>
3067          Check_Array_Or_Scalar_Type;
3068
3069       --------------
3070       -- Last_Bit --
3071       --------------
3072
3073       when Attribute_Last_Bit =>
3074          Check_Component;
3075          Set_Etype (N, Universal_Integer);
3076
3077       ------------------
3078       -- Leading_Part --
3079       ------------------
3080
3081       when Attribute_Leading_Part =>
3082          Check_Floating_Point_Type_2;
3083          Set_Etype (N, P_Base_Type);
3084          Resolve (E1, P_Base_Type);
3085          Resolve (E2, Any_Integer);
3086
3087       ------------
3088       -- Length --
3089       ------------
3090
3091       when Attribute_Length =>
3092          Check_Array_Type;
3093          Set_Etype (N, Universal_Integer);
3094
3095       -------------
3096       -- Machine --
3097       -------------
3098
3099       when Attribute_Machine =>
3100          Check_Floating_Point_Type_1;
3101          Set_Etype (N, P_Base_Type);
3102          Resolve (E1, P_Base_Type);
3103
3104       ------------------
3105       -- Machine_Emax --
3106       ------------------
3107
3108       when Attribute_Machine_Emax =>
3109          Check_Floating_Point_Type_0;
3110          Set_Etype (N, Universal_Integer);
3111
3112       ------------------
3113       -- Machine_Emin --
3114       ------------------
3115
3116       when Attribute_Machine_Emin =>
3117          Check_Floating_Point_Type_0;
3118          Set_Etype (N, Universal_Integer);
3119
3120       ----------------------
3121       -- Machine_Mantissa --
3122       ----------------------
3123
3124       when Attribute_Machine_Mantissa =>
3125          Check_Floating_Point_Type_0;
3126          Set_Etype (N, Universal_Integer);
3127
3128       -----------------------
3129       -- Machine_Overflows --
3130       -----------------------
3131
3132       when Attribute_Machine_Overflows =>
3133          Check_Real_Type;
3134          Check_E0;
3135          Set_Etype (N, Standard_Boolean);
3136
3137       -------------------
3138       -- Machine_Radix --
3139       -------------------
3140
3141       when Attribute_Machine_Radix =>
3142          Check_Real_Type;
3143          Check_E0;
3144          Set_Etype (N, Universal_Integer);
3145
3146       ----------------------
3147       -- Machine_Rounding --
3148       ----------------------
3149
3150       when Attribute_Machine_Rounding =>
3151          Check_Floating_Point_Type_1;
3152          Set_Etype (N, P_Base_Type);
3153          Resolve (E1, P_Base_Type);
3154
3155       --------------------
3156       -- Machine_Rounds --
3157       --------------------
3158
3159       when Attribute_Machine_Rounds =>
3160          Check_Real_Type;
3161          Check_E0;
3162          Set_Etype (N, Standard_Boolean);
3163
3164       ------------------
3165       -- Machine_Size --
3166       ------------------
3167
3168       when Attribute_Machine_Size =>
3169          Check_E0;
3170          Check_Type;
3171          Check_Not_Incomplete_Type;
3172          Set_Etype (N, Universal_Integer);
3173
3174       --------------
3175       -- Mantissa --
3176       --------------
3177
3178       when Attribute_Mantissa =>
3179          Check_E0;
3180          Check_Real_Type;
3181          Set_Etype (N, Universal_Integer);
3182
3183       ---------
3184       -- Max --
3185       ---------
3186
3187       when Attribute_Max =>
3188          Check_E2;
3189          Check_Scalar_Type;
3190          Resolve (E1, P_Base_Type);
3191          Resolve (E2, P_Base_Type);
3192          Set_Etype (N, P_Base_Type);
3193
3194       ----------------------------------
3195       -- Max_Size_In_Storage_Elements --
3196       ----------------------------------
3197
3198       when Attribute_Max_Size_In_Storage_Elements =>
3199          Check_E0;
3200          Check_Type;
3201          Check_Not_Incomplete_Type;
3202          Set_Etype (N, Universal_Integer);
3203
3204       -----------------------
3205       -- Maximum_Alignment --
3206       -----------------------
3207
3208       when Attribute_Maximum_Alignment =>
3209          Standard_Attribute (Ttypes.Maximum_Alignment);
3210
3211       --------------------
3212       -- Mechanism_Code --
3213       --------------------
3214
3215       when Attribute_Mechanism_Code =>
3216          if not Is_Entity_Name (P)
3217            or else not Is_Subprogram (Entity (P))
3218          then
3219             Error_Attr_P ("prefix of % attribute must be subprogram");
3220          end if;
3221
3222          Check_Either_E0_Or_E1;
3223
3224          if Present (E1) then
3225             Resolve (E1, Any_Integer);
3226             Set_Etype (E1, Standard_Integer);
3227
3228             if not Is_Static_Expression (E1) then
3229                Flag_Non_Static_Expr
3230                  ("expression for parameter number must be static!", E1);
3231                Error_Attr;
3232
3233             elsif UI_To_Int (Intval (E1)) > Number_Formals (Entity (P))
3234               or else UI_To_Int (Intval (E1)) < 0
3235             then
3236                Error_Attr ("invalid parameter number for %attribute", E1);
3237             end if;
3238          end if;
3239
3240          Set_Etype (N, Universal_Integer);
3241
3242       ---------
3243       -- Min --
3244       ---------
3245
3246       when Attribute_Min =>
3247          Check_E2;
3248          Check_Scalar_Type;
3249          Resolve (E1, P_Base_Type);
3250          Resolve (E2, P_Base_Type);
3251          Set_Etype (N, P_Base_Type);
3252
3253       ---------
3254       -- Mod --
3255       ---------
3256
3257       when Attribute_Mod =>
3258
3259          --  Note: this attribute is only allowed in Ada 2005 mode, but
3260          --  we do not need to test that here, since Mod is only recognized
3261          --  as an attribute name in Ada 2005 mode during the parse.
3262
3263          Check_E1;
3264          Check_Modular_Integer_Type;
3265          Resolve (E1, Any_Integer);
3266          Set_Etype (N, P_Base_Type);
3267
3268       -----------
3269       -- Model --
3270       -----------
3271
3272       when Attribute_Model =>
3273          Check_Floating_Point_Type_1;
3274          Set_Etype (N, P_Base_Type);
3275          Resolve (E1, P_Base_Type);
3276
3277       ----------------
3278       -- Model_Emin --
3279       ----------------
3280
3281       when Attribute_Model_Emin =>
3282          Check_Floating_Point_Type_0;
3283          Set_Etype (N, Universal_Integer);
3284
3285       -------------------
3286       -- Model_Epsilon --
3287       -------------------
3288
3289       when Attribute_Model_Epsilon =>
3290          Check_Floating_Point_Type_0;
3291          Set_Etype (N, Universal_Real);
3292
3293       --------------------
3294       -- Model_Mantissa --
3295       --------------------
3296
3297       when Attribute_Model_Mantissa =>
3298          Check_Floating_Point_Type_0;
3299          Set_Etype (N, Universal_Integer);
3300
3301       -----------------
3302       -- Model_Small --
3303       -----------------
3304
3305       when Attribute_Model_Small =>
3306          Check_Floating_Point_Type_0;
3307          Set_Etype (N, Universal_Real);
3308
3309       -------------
3310       -- Modulus --
3311       -------------
3312
3313       when Attribute_Modulus =>
3314          Check_E0;
3315          Check_Modular_Integer_Type;
3316          Set_Etype (N, Universal_Integer);
3317
3318       --------------------
3319       -- Null_Parameter --
3320       --------------------
3321
3322       when Attribute_Null_Parameter => Null_Parameter : declare
3323          Parnt  : constant Node_Id := Parent (N);
3324          GParnt : constant Node_Id := Parent (Parnt);
3325
3326          procedure Bad_Null_Parameter (Msg : String);
3327          --  Used if bad Null parameter attribute node is found. Issues
3328          --  given error message, and also sets the type to Any_Type to
3329          --  avoid blowups later on from dealing with a junk node.
3330
3331          procedure Must_Be_Imported (Proc_Ent : Entity_Id);
3332          --  Called to check that Proc_Ent is imported subprogram
3333
3334          ------------------------
3335          -- Bad_Null_Parameter --
3336          ------------------------
3337
3338          procedure Bad_Null_Parameter (Msg : String) is
3339          begin
3340             Error_Msg_N (Msg, N);
3341             Set_Etype (N, Any_Type);
3342          end Bad_Null_Parameter;
3343
3344          ----------------------
3345          -- Must_Be_Imported --
3346          ----------------------
3347
3348          procedure Must_Be_Imported (Proc_Ent : Entity_Id) is
3349             Pent : Entity_Id := Proc_Ent;
3350
3351          begin
3352             while Present (Alias (Pent)) loop
3353                Pent := Alias (Pent);
3354             end loop;
3355
3356             --  Ignore check if procedure not frozen yet (we will get
3357             --  another chance when the default parameter is reanalyzed)
3358
3359             if not Is_Frozen (Pent) then
3360                return;
3361
3362             elsif not Is_Imported (Pent) then
3363                Bad_Null_Parameter
3364                  ("Null_Parameter can only be used with imported subprogram");
3365
3366             else
3367                return;
3368             end if;
3369          end Must_Be_Imported;
3370
3371       --  Start of processing for Null_Parameter
3372
3373       begin
3374          Check_Type;
3375          Check_E0;
3376          Set_Etype (N, P_Type);
3377
3378          --  Case of attribute used as default expression
3379
3380          if Nkind (Parnt) = N_Parameter_Specification then
3381             Must_Be_Imported (Defining_Entity (GParnt));
3382
3383          --  Case of attribute used as actual for subprogram (positional)
3384
3385          elsif (Nkind (Parnt) = N_Procedure_Call_Statement
3386                  or else
3387                 Nkind (Parnt) = N_Function_Call)
3388             and then Is_Entity_Name (Name (Parnt))
3389          then
3390             Must_Be_Imported (Entity (Name (Parnt)));
3391
3392          --  Case of attribute used as actual for subprogram (named)
3393
3394          elsif Nkind (Parnt) = N_Parameter_Association
3395            and then (Nkind (GParnt) = N_Procedure_Call_Statement
3396                        or else
3397                      Nkind (GParnt) = N_Function_Call)
3398            and then Is_Entity_Name (Name (GParnt))
3399          then
3400             Must_Be_Imported (Entity (Name (GParnt)));
3401
3402          --  Not an allowed case
3403
3404          else
3405             Bad_Null_Parameter
3406               ("Null_Parameter must be actual or default parameter");
3407          end if;
3408
3409       end Null_Parameter;
3410
3411       -----------------
3412       -- Object_Size --
3413       -----------------
3414
3415       when Attribute_Object_Size =>
3416          Check_E0;
3417          Check_Type;
3418          Check_Not_Incomplete_Type;
3419          Set_Etype (N, Universal_Integer);
3420
3421       ------------
3422       -- Output --
3423       ------------
3424
3425       when Attribute_Output =>
3426          Check_E2;
3427          Check_Stream_Attribute (TSS_Stream_Output);
3428          Set_Etype (N, Standard_Void_Type);
3429          Resolve (N, Standard_Void_Type);
3430
3431       ------------------
3432       -- Partition_ID --
3433       ------------------
3434
3435       when Attribute_Partition_ID =>
3436          Check_E0;
3437
3438          if P_Type /= Any_Type then
3439             if not Is_Library_Level_Entity (Entity (P)) then
3440                Error_Attr_P
3441                  ("prefix of % attribute must be library-level entity");
3442
3443             --  The defining entity of prefix should not be declared inside
3444             --  a Pure unit. RM E.1(8).
3445             --  The Is_Pure flag has been set during declaration.
3446
3447             elsif Is_Entity_Name (P)
3448               and then Is_Pure (Entity (P))
3449             then
3450                Error_Attr_P
3451                  ("prefix of % attribute must not be declared pure");
3452             end if;
3453          end if;
3454
3455          Set_Etype (N, Universal_Integer);
3456
3457       -------------------------
3458       -- Passed_By_Reference --
3459       -------------------------
3460
3461       when Attribute_Passed_By_Reference =>
3462          Check_E0;
3463          Check_Type;
3464          Set_Etype (N, Standard_Boolean);
3465
3466       ------------------
3467       -- Pool_Address --
3468       ------------------
3469
3470       when Attribute_Pool_Address =>
3471          Check_E0;
3472          Set_Etype (N, RTE (RE_Address));
3473
3474       ---------
3475       -- Pos --
3476       ---------
3477
3478       when Attribute_Pos =>
3479          Check_Discrete_Type;
3480          Check_E1;
3481          Resolve (E1, P_Base_Type);
3482          Set_Etype (N, Universal_Integer);
3483
3484       --------------
3485       -- Position --
3486       --------------
3487
3488       when Attribute_Position =>
3489          Check_Component;
3490          Set_Etype (N, Universal_Integer);
3491
3492       ----------
3493       -- Pred --
3494       ----------
3495
3496       when Attribute_Pred =>
3497          Check_Scalar_Type;
3498          Check_E1;
3499          Resolve (E1, P_Base_Type);
3500          Set_Etype (N, P_Base_Type);
3501
3502          --  Nothing to do for real type case
3503
3504          if Is_Real_Type (P_Type) then
3505             null;
3506
3507          --  If not modular type, test for overflow check required
3508
3509          else
3510             if not Is_Modular_Integer_Type (P_Type)
3511               and then not Range_Checks_Suppressed (P_Base_Type)
3512             then
3513                Enable_Range_Check (E1);
3514             end if;
3515          end if;
3516
3517       --------------
3518       -- Priority --
3519       --------------
3520
3521       --  Ada 2005 (AI-327): Dynamic ceiling priorities
3522
3523       when Attribute_Priority =>
3524          if Ada_Version < Ada_05 then
3525             Error_Attr ("% attribute is allowed only in Ada 2005 mode", P);
3526          end if;
3527
3528          Check_E0;
3529
3530          --  The prefix must be a protected object (AARM D.5.2 (2/2))
3531
3532          Analyze (P);
3533
3534          if Is_Protected_Type (Etype (P))
3535            or else (Is_Access_Type (Etype (P))
3536                       and then Is_Protected_Type (Designated_Type (Etype (P))))
3537          then
3538             Resolve (P, Etype (P));
3539          else
3540             Error_Attr_P ("prefix of % attribute must be a protected object");
3541          end if;
3542
3543          Set_Etype (N, Standard_Integer);
3544
3545          --  Must be called from within a protected procedure or entry of the
3546          --  protected object.
3547
3548          declare
3549             S : Entity_Id;
3550
3551          begin
3552             S := Current_Scope;
3553             while S /= Etype (P)
3554                and then S /= Standard_Standard
3555             loop
3556                S := Scope (S);
3557             end loop;
3558
3559             if S = Standard_Standard then
3560                Error_Attr ("the attribute % is only allowed inside protected "
3561                            & "operations", P);
3562             end if;
3563          end;
3564
3565          Validate_Non_Static_Attribute_Function_Call;
3566
3567       -----------
3568       -- Range --
3569       -----------
3570
3571       when Attribute_Range =>
3572          Check_Array_Or_Scalar_Type;
3573
3574          if Ada_Version = Ada_83
3575            and then Is_Scalar_Type (P_Type)
3576            and then Comes_From_Source (N)
3577          then
3578             Error_Attr
3579               ("(Ada 83) % attribute not allowed for scalar type", P);
3580          end if;
3581
3582       ------------------
3583       -- Range_Length --
3584       ------------------
3585
3586       when Attribute_Range_Length =>
3587          Check_Discrete_Type;
3588          Set_Etype (N, Universal_Integer);
3589
3590       ----------
3591       -- Read --
3592       ----------
3593
3594       when Attribute_Read =>
3595          Check_E2;
3596          Check_Stream_Attribute (TSS_Stream_Read);
3597          Set_Etype (N, Standard_Void_Type);
3598          Resolve (N, Standard_Void_Type);
3599          Note_Possible_Modification (E2);
3600
3601       ---------------
3602       -- Remainder --
3603       ---------------
3604
3605       when Attribute_Remainder =>
3606          Check_Floating_Point_Type_2;
3607          Set_Etype (N, P_Base_Type);
3608          Resolve (E1, P_Base_Type);
3609          Resolve (E2, P_Base_Type);
3610
3611       -----------
3612       -- Round --
3613       -----------
3614
3615       when Attribute_Round =>
3616          Check_E1;
3617          Check_Decimal_Fixed_Point_Type;
3618          Set_Etype (N, P_Base_Type);
3619
3620          --  Because the context is universal_real (3.5.10(12)) it is a legal
3621          --  context for a universal fixed expression. This is the only
3622          --  attribute whose functional description involves U_R.
3623
3624          if Etype (E1) = Universal_Fixed then
3625             declare
3626                Conv : constant Node_Id := Make_Type_Conversion (Loc,
3627                   Subtype_Mark => New_Occurrence_Of (Universal_Real, Loc),
3628                   Expression   => Relocate_Node (E1));
3629
3630             begin
3631                Rewrite (E1, Conv);
3632                Analyze (E1);
3633             end;
3634          end if;
3635
3636          Resolve (E1, Any_Real);
3637
3638       --------------
3639       -- Rounding --
3640       --------------
3641
3642       when Attribute_Rounding =>
3643          Check_Floating_Point_Type_1;
3644          Set_Etype (N, P_Base_Type);
3645          Resolve (E1, P_Base_Type);
3646
3647       ---------------
3648       -- Safe_Emax --
3649       ---------------
3650
3651       when Attribute_Safe_Emax =>
3652          Check_Floating_Point_Type_0;
3653          Set_Etype (N, Universal_Integer);
3654
3655       ----------------
3656       -- Safe_First --
3657       ----------------
3658
3659       when Attribute_Safe_First =>
3660          Check_Floating_Point_Type_0;
3661          Set_Etype (N, Universal_Real);
3662
3663       ----------------
3664       -- Safe_Large --
3665       ----------------
3666
3667       when Attribute_Safe_Large =>
3668          Check_E0;
3669          Check_Real_Type;
3670          Set_Etype (N, Universal_Real);
3671
3672       ---------------
3673       -- Safe_Last --
3674       ---------------
3675
3676       when Attribute_Safe_Last =>
3677          Check_Floating_Point_Type_0;
3678          Set_Etype (N, Universal_Real);
3679
3680       ----------------
3681       -- Safe_Small --
3682       ----------------
3683
3684       when Attribute_Safe_Small =>
3685          Check_E0;
3686          Check_Real_Type;
3687          Set_Etype (N, Universal_Real);
3688
3689       -----------
3690       -- Scale --
3691       -----------
3692
3693       when Attribute_Scale =>
3694          Check_E0;
3695          Check_Decimal_Fixed_Point_Type;
3696          Set_Etype (N, Universal_Integer);
3697
3698       -------------
3699       -- Scaling --
3700       -------------
3701
3702       when Attribute_Scaling =>
3703          Check_Floating_Point_Type_2;
3704          Set_Etype (N, P_Base_Type);
3705          Resolve (E1, P_Base_Type);
3706
3707       ------------------
3708       -- Signed_Zeros --
3709       ------------------
3710
3711       when Attribute_Signed_Zeros =>
3712          Check_Floating_Point_Type_0;
3713          Set_Etype (N, Standard_Boolean);
3714
3715       ----------
3716       -- Size --
3717       ----------
3718
3719       when Attribute_Size | Attribute_VADS_Size =>
3720          Check_E0;
3721
3722          --  If prefix is parameterless function call, rewrite and resolve
3723          --  as such.
3724
3725          if Is_Entity_Name (P)
3726            and then Ekind (Entity (P)) = E_Function
3727          then
3728             Resolve (P);
3729
3730          --  Similar processing for a protected function call
3731
3732          elsif Nkind (P) = N_Selected_Component
3733            and then Ekind (Entity (Selector_Name (P))) = E_Function
3734          then
3735             Resolve (P);
3736          end if;
3737
3738          if Is_Object_Reference (P) then
3739             Check_Object_Reference (P);
3740
3741          elsif Is_Entity_Name (P)
3742            and then (Is_Type (Entity (P))
3743                        or else Ekind (Entity (P)) = E_Enumeration_Literal)
3744          then
3745             null;
3746
3747          elsif Nkind (P) = N_Type_Conversion
3748            and then not Comes_From_Source (P)
3749          then
3750             null;
3751
3752          else
3753             Error_Attr_P ("invalid prefix for % attribute");
3754          end if;
3755
3756          Check_Not_Incomplete_Type;
3757          Set_Etype (N, Universal_Integer);
3758
3759       -----------
3760       -- Small --
3761       -----------
3762
3763       when Attribute_Small =>
3764          Check_E0;
3765          Check_Real_Type;
3766          Set_Etype (N, Universal_Real);
3767
3768       ------------------
3769       -- Storage_Pool --
3770       ------------------
3771
3772       when Attribute_Storage_Pool =>
3773          if Is_Access_Type (P_Type) then
3774             Check_E0;
3775
3776             if Ekind (P_Type) = E_Access_Subprogram_Type then
3777                Error_Attr_P
3778                  ("cannot use % attribute for access-to-subprogram type");
3779             end if;
3780
3781             --  Set appropriate entity
3782
3783             if Present (Associated_Storage_Pool (Root_Type (P_Type))) then
3784                Set_Entity (N, Associated_Storage_Pool (Root_Type (P_Type)));
3785             else
3786                Set_Entity (N, RTE (RE_Global_Pool_Object));
3787             end if;
3788
3789             Set_Etype (N, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
3790
3791             --  Validate_Remote_Access_To_Class_Wide_Type for attribute
3792             --  Storage_Pool since this attribute is not defined for such
3793             --  types (RM E.2.3(22)).
3794
3795             Validate_Remote_Access_To_Class_Wide_Type (N);
3796
3797          else
3798             Error_Attr_P ("prefix of % attribute must be access type");
3799          end if;
3800
3801       ------------------
3802       -- Storage_Size --
3803       ------------------
3804
3805       when Attribute_Storage_Size =>
3806          if Is_Task_Type (P_Type) then
3807             Check_E0;
3808             Set_Etype (N, Universal_Integer);
3809
3810          elsif Is_Access_Type (P_Type) then
3811             if Ekind (P_Type) = E_Access_Subprogram_Type then
3812                Error_Attr_P
3813                  ("cannot use % attribute for access-to-subprogram type");
3814             end if;
3815
3816             if Is_Entity_Name (P)
3817               and then Is_Type (Entity (P))
3818             then
3819                Check_E0;
3820                Check_Type;
3821                Set_Etype (N, Universal_Integer);
3822
3823                --   Validate_Remote_Access_To_Class_Wide_Type for attribute
3824                --   Storage_Size since this attribute is not defined for
3825                --   such types (RM E.2.3(22)).
3826
3827                Validate_Remote_Access_To_Class_Wide_Type (N);
3828
3829             --  The prefix is allowed to be an implicit dereference
3830             --  of an access value designating a task.
3831
3832             else
3833                Check_E0;
3834                Check_Task_Prefix;
3835                Set_Etype (N, Universal_Integer);
3836             end if;
3837
3838          else
3839             Error_Attr_P ("prefix of % attribute must be access or task type");
3840          end if;
3841
3842       ------------------
3843       -- Storage_Unit --
3844       ------------------
3845
3846       when Attribute_Storage_Unit =>
3847          Standard_Attribute (Ttypes.System_Storage_Unit);
3848
3849       -----------------
3850       -- Stream_Size --
3851       -----------------
3852
3853       when Attribute_Stream_Size =>
3854          Check_E0;
3855          Check_Type;
3856
3857          if Is_Entity_Name (P)
3858            and then Is_Elementary_Type (Entity (P))
3859          then
3860             Set_Etype (N, Universal_Integer);
3861          else
3862             Error_Attr_P ("invalid prefix for % attribute");
3863          end if;
3864
3865       ---------------
3866       -- Stub_Type --
3867       ---------------
3868
3869       when Attribute_Stub_Type =>
3870          Check_Type;
3871          Check_E0;
3872
3873          if Is_Remote_Access_To_Class_Wide_Type (P_Type) then
3874             Rewrite (N,
3875               New_Occurrence_Of (Corresponding_Stub_Type (P_Type), Loc));
3876          else
3877             Error_Attr_P
3878               ("prefix of% attribute must be remote access to classwide");
3879          end if;
3880
3881       ----------
3882       -- Succ --
3883       ----------
3884
3885       when Attribute_Succ =>
3886          Check_Scalar_Type;
3887          Check_E1;
3888          Resolve (E1, P_Base_Type);
3889          Set_Etype (N, P_Base_Type);
3890
3891          --  Nothing to do for real type case
3892
3893          if Is_Real_Type (P_Type) then
3894             null;
3895
3896          --  If not modular type, test for overflow check required
3897
3898          else
3899             if not Is_Modular_Integer_Type (P_Type)
3900               and then not Range_Checks_Suppressed (P_Base_Type)
3901             then
3902                Enable_Range_Check (E1);
3903             end if;
3904          end if;
3905
3906       ---------
3907       -- Tag --
3908       ---------
3909
3910       when Attribute_Tag =>
3911          Check_E0;
3912          Check_Dereference;
3913
3914          if not Is_Tagged_Type (P_Type) then
3915             Error_Attr_P ("prefix of % attribute must be tagged");
3916
3917          --  Next test does not apply to generated code
3918          --  why not, and what does the illegal reference mean???
3919
3920          elsif Is_Object_Reference (P)
3921            and then not Is_Class_Wide_Type (P_Type)
3922            and then Comes_From_Source (N)
3923          then
3924             Error_Attr_P
3925               ("% attribute can only be applied to objects " &
3926                "of class - wide type");
3927          end if;
3928
3929          --  The prefix cannot be an incomplete type. However, references
3930          --  to 'Tag can be generated when expanding interface conversions,
3931          --  and this is legal.
3932
3933          if Comes_From_Source (N) then
3934             Check_Not_Incomplete_Type;
3935          end if;
3936          Set_Etype (N, RTE (RE_Tag));
3937
3938       -----------------
3939       -- Target_Name --
3940       -----------------
3941
3942       when Attribute_Target_Name => Target_Name : declare
3943          TN : constant String := Sdefault.Target_Name.all;
3944          TL : Natural;
3945
3946       begin
3947          Check_Standard_Prefix;
3948          Check_E0;
3949
3950          TL := TN'Last;
3951
3952          if TN (TL) = '/' or else TN (TL) = '\' then
3953             TL := TL - 1;
3954          end if;
3955
3956          Rewrite (N,
3957            Make_String_Literal (Loc,
3958              Strval => TN (TN'First .. TL)));
3959          Analyze_And_Resolve (N, Standard_String);
3960       end Target_Name;
3961
3962       ----------------
3963       -- Terminated --
3964       ----------------
3965
3966       when Attribute_Terminated =>
3967          Check_E0;
3968          Set_Etype (N, Standard_Boolean);
3969          Check_Task_Prefix;
3970
3971       ----------------
3972       -- To_Address --
3973       ----------------
3974
3975       when Attribute_To_Address =>
3976          Check_E1;
3977          Analyze (P);
3978
3979          if Nkind (P) /= N_Identifier
3980            or else Chars (P) /= Name_System
3981          then
3982             Error_Attr_P ("prefix of %attribute must be System");
3983          end if;
3984
3985          Generate_Reference (RTE (RE_Address), P);
3986          Analyze_And_Resolve (E1, Any_Integer);
3987          Set_Etype (N, RTE (RE_Address));
3988
3989       ----------------
3990       -- Truncation --
3991       ----------------
3992
3993       when Attribute_Truncation =>
3994          Check_Floating_Point_Type_1;
3995          Resolve (E1, P_Base_Type);
3996          Set_Etype (N, P_Base_Type);
3997
3998       ----------------
3999       -- Type_Class --
4000       ----------------
4001
4002       when Attribute_Type_Class =>
4003          Check_E0;
4004          Check_Type;
4005          Check_Not_Incomplete_Type;
4006          Set_Etype (N, RTE (RE_Type_Class));
4007
4008       -----------------
4009       -- UET_Address --
4010       -----------------
4011
4012       when Attribute_UET_Address =>
4013          Check_E0;
4014          Check_Unit_Name (P);
4015          Set_Etype (N, RTE (RE_Address));
4016
4017       -----------------------
4018       -- Unbiased_Rounding --
4019       -----------------------
4020
4021       when Attribute_Unbiased_Rounding =>
4022          Check_Floating_Point_Type_1;
4023          Set_Etype (N, P_Base_Type);
4024          Resolve (E1, P_Base_Type);
4025
4026       ----------------------
4027       -- Unchecked_Access --
4028       ----------------------
4029
4030       when Attribute_Unchecked_Access =>
4031          if Comes_From_Source (N) then
4032             Check_Restriction (No_Unchecked_Access, N);
4033          end if;
4034
4035          Analyze_Access_Attribute;
4036
4037       -------------------------
4038       -- Unconstrained_Array --
4039       -------------------------
4040
4041       when Attribute_Unconstrained_Array =>
4042          Check_E0;
4043          Check_Type;
4044          Check_Not_Incomplete_Type;
4045          Set_Etype (N, Standard_Boolean);
4046
4047       ------------------------------
4048       -- Universal_Literal_String --
4049       ------------------------------
4050
4051       --  This is a GNAT specific attribute whose prefix must be a named
4052       --  number where the expression is either a single numeric literal,
4053       --  or a numeric literal immediately preceded by a minus sign. The
4054       --  result is equivalent to a string literal containing the text of
4055       --  the literal as it appeared in the source program with a possible
4056       --  leading minus sign.
4057
4058       when Attribute_Universal_Literal_String => Universal_Literal_String :
4059       begin
4060          Check_E0;
4061
4062          if not Is_Entity_Name (P)
4063            or else Ekind (Entity (P)) not in Named_Kind
4064          then
4065             Error_Attr_P ("prefix for % attribute must be named number");
4066
4067          else
4068             declare
4069                Expr     : Node_Id;
4070                Negative : Boolean;
4071                S        : Source_Ptr;
4072                Src      : Source_Buffer_Ptr;
4073
4074             begin
4075                Expr := Original_Node (Expression (Parent (Entity (P))));
4076
4077                if Nkind (Expr) = N_Op_Minus then
4078                   Negative := True;
4079                   Expr := Original_Node (Right_Opnd (Expr));
4080                else
4081                   Negative := False;
4082                end if;
4083
4084                if Nkind (Expr) /= N_Integer_Literal
4085                  and then Nkind (Expr) /= N_Real_Literal
4086                then
4087                   Error_Attr
4088                     ("named number for % attribute must be simple literal", N);
4089                end if;
4090
4091                --  Build string literal corresponding to source literal text
4092
4093                Start_String;
4094
4095                if Negative then
4096                   Store_String_Char (Get_Char_Code ('-'));
4097                end if;
4098
4099                S := Sloc (Expr);
4100                Src := Source_Text (Get_Source_File_Index (S));
4101
4102                while Src (S) /= ';' and then Src (S) /= ' ' loop
4103                   Store_String_Char (Get_Char_Code (Src (S)));
4104                   S := S + 1;
4105                end loop;
4106
4107                --  Now we rewrite the attribute with the string literal
4108
4109                Rewrite (N,
4110                  Make_String_Literal (Loc, End_String));
4111                Analyze (N);
4112             end;
4113          end if;
4114       end Universal_Literal_String;
4115
4116       -------------------------
4117       -- Unrestricted_Access --
4118       -------------------------
4119
4120       --  This is a GNAT specific attribute which is like Access except that
4121       --  all scope checks and checks for aliased views are omitted.
4122
4123       when Attribute_Unrestricted_Access =>
4124          if Comes_From_Source (N) then
4125             Check_Restriction (No_Unchecked_Access, N);
4126          end if;
4127
4128          if Is_Entity_Name (P) then
4129             Set_Address_Taken (Entity (P));
4130          end if;
4131
4132          Analyze_Access_Attribute;
4133
4134       ---------
4135       -- Val --
4136       ---------
4137
4138       when Attribute_Val => Val : declare
4139       begin
4140          Check_E1;
4141          Check_Discrete_Type;
4142          Resolve (E1, Any_Integer);
4143          Set_Etype (N, P_Base_Type);
4144
4145          --  Note, we need a range check in general, but we wait for the
4146          --  Resolve call to do this, since we want to let Eval_Attribute
4147          --  have a chance to find an static illegality first!
4148       end Val;
4149
4150       -----------
4151       -- Valid --
4152       -----------
4153
4154       when Attribute_Valid =>
4155          Check_E0;
4156
4157          --  Ignore check for object if we have a 'Valid reference generated
4158          --  by the expanded code, since in some cases valid checks can occur
4159          --  on items that are names, but are not objects (e.g. attributes).
4160
4161          if Comes_From_Source (N) then
4162             Check_Object_Reference (P);
4163          end if;
4164
4165          if not Is_Scalar_Type (P_Type) then
4166             Error_Attr_P ("object for % attribute must be of scalar type");
4167          end if;
4168
4169          Set_Etype (N, Standard_Boolean);
4170
4171       -----------
4172       -- Value --
4173       -----------
4174
4175       when Attribute_Value => Value :
4176       begin
4177          Check_E1;
4178          Check_Scalar_Type;
4179
4180          --  Case of enumeration type
4181
4182          if Is_Enumeration_Type (P_Type) then
4183             Check_Restriction (No_Enumeration_Maps, N);
4184
4185             --  Mark all enumeration literals as referenced, since the use of
4186             --  the Value attribute can implicitly reference any of the
4187             --  literals of the enumeration base type.
4188
4189             declare
4190                Ent : Entity_Id := First_Literal (P_Base_Type);
4191             begin
4192                while Present (Ent) loop
4193                   Set_Referenced (Ent);
4194                   Next_Literal (Ent);
4195                end loop;
4196             end;
4197          end if;
4198
4199          --  Set Etype before resolving expression because expansion of
4200          --  expression may require enclosing type. Note that the type
4201          --  returned by 'Value is the base type of the prefix type.
4202
4203          Set_Etype (N, P_Base_Type);
4204          Validate_Non_Static_Attribute_Function_Call;
4205       end Value;
4206
4207       ----------------
4208       -- Value_Size --
4209       ----------------
4210
4211       when Attribute_Value_Size =>
4212          Check_E0;
4213          Check_Type;
4214          Check_Not_Incomplete_Type;
4215          Set_Etype (N, Universal_Integer);
4216
4217       -------------
4218       -- Version --
4219       -------------
4220
4221       when Attribute_Version =>
4222          Check_E0;
4223          Check_Program_Unit;
4224          Set_Etype (N, RTE (RE_Version_String));
4225
4226       ------------------
4227       -- Wchar_T_Size --
4228       ------------------
4229
4230       when Attribute_Wchar_T_Size =>
4231          Standard_Attribute (Interfaces_Wchar_T_Size);
4232
4233       ----------------
4234       -- Wide_Image --
4235       ----------------
4236
4237       when Attribute_Wide_Image => Wide_Image :
4238       begin
4239          Check_Scalar_Type;
4240          Set_Etype (N, Standard_Wide_String);
4241          Check_E1;
4242          Resolve (E1, P_Base_Type);
4243          Validate_Non_Static_Attribute_Function_Call;
4244       end Wide_Image;
4245
4246       ---------------------
4247       -- Wide_Wide_Image --
4248       ---------------------
4249
4250       when Attribute_Wide_Wide_Image => Wide_Wide_Image :
4251       begin
4252          Check_Scalar_Type;
4253          Set_Etype (N, Standard_Wide_Wide_String);
4254          Check_E1;
4255          Resolve (E1, P_Base_Type);
4256          Validate_Non_Static_Attribute_Function_Call;
4257       end Wide_Wide_Image;
4258
4259       ----------------
4260       -- Wide_Value --
4261       ----------------
4262
4263       when Attribute_Wide_Value => Wide_Value :
4264       begin
4265          Check_E1;
4266          Check_Scalar_Type;
4267
4268          --  Set Etype before resolving expression because expansion
4269          --  of expression may require enclosing type.
4270
4271          Set_Etype (N, P_Type);
4272          Validate_Non_Static_Attribute_Function_Call;
4273       end Wide_Value;
4274
4275       ---------------------
4276       -- Wide_Wide_Value --
4277       ---------------------
4278
4279       when Attribute_Wide_Wide_Value => Wide_Wide_Value :
4280       begin
4281          Check_E1;
4282          Check_Scalar_Type;
4283
4284          --  Set Etype before resolving expression because expansion
4285          --  of expression may require enclosing type.
4286
4287          Set_Etype (N, P_Type);
4288          Validate_Non_Static_Attribute_Function_Call;
4289       end Wide_Wide_Value;
4290
4291       ---------------------
4292       -- Wide_Wide_Width --
4293       ---------------------
4294
4295       when Attribute_Wide_Wide_Width =>
4296          Check_E0;
4297          Check_Scalar_Type;
4298          Set_Etype (N, Universal_Integer);
4299
4300       ----------------
4301       -- Wide_Width --
4302       ----------------
4303
4304       when Attribute_Wide_Width =>
4305          Check_E0;
4306          Check_Scalar_Type;
4307          Set_Etype (N, Universal_Integer);
4308
4309       -----------
4310       -- Width --
4311       -----------
4312
4313       when Attribute_Width =>
4314          Check_E0;
4315          Check_Scalar_Type;
4316          Set_Etype (N, Universal_Integer);
4317
4318       ---------------
4319       -- Word_Size --
4320       ---------------
4321
4322       when Attribute_Word_Size =>
4323          Standard_Attribute (System_Word_Size);
4324
4325       -----------
4326       -- Write --
4327       -----------
4328
4329       when Attribute_Write =>
4330          Check_E2;
4331          Check_Stream_Attribute (TSS_Stream_Write);
4332          Set_Etype (N, Standard_Void_Type);
4333          Resolve (N, Standard_Void_Type);
4334
4335       end case;
4336
4337    --  All errors raise Bad_Attribute, so that we get out before any further
4338    --  damage occurs when an error is detected (for example, if we check for
4339    --  one attribute expression, and the check succeeds, we want to be able
4340    --  to proceed securely assuming that an expression is in fact present.
4341
4342    --  Note: we set the attribute analyzed in this case to prevent any
4343    --  attempt at reanalysis which could generate spurious error msgs.
4344
4345    exception
4346       when Bad_Attribute =>
4347          Set_Analyzed (N);
4348          Set_Etype (N, Any_Type);
4349          return;
4350    end Analyze_Attribute;
4351
4352    --------------------
4353    -- Eval_Attribute --
4354    --------------------
4355
4356    procedure Eval_Attribute (N : Node_Id) is
4357       Loc   : constant Source_Ptr   := Sloc (N);
4358       Aname : constant Name_Id      := Attribute_Name (N);
4359       Id    : constant Attribute_Id := Get_Attribute_Id (Aname);
4360       P     : constant Node_Id      := Prefix (N);
4361
4362       C_Type : constant Entity_Id := Etype (N);
4363       --  The type imposed by the context
4364
4365       E1 : Node_Id;
4366       --  First expression, or Empty if none
4367
4368       E2 : Node_Id;
4369       --  Second expression, or Empty if none
4370
4371       P_Entity : Entity_Id;
4372       --  Entity denoted by prefix
4373
4374       P_Type : Entity_Id;
4375       --  The type of the prefix
4376
4377       P_Base_Type : Entity_Id;
4378       --  The base type of the prefix type
4379
4380       P_Root_Type : Entity_Id;
4381       --  The root type of the prefix type
4382
4383       Static : Boolean;
4384       --  True if the result is Static. This is set by the general processing
4385       --  to true if the prefix is static, and all expressions are static. It
4386       --  can be reset as processing continues for particular attributes
4387
4388       Lo_Bound, Hi_Bound : Node_Id;
4389       --  Expressions for low and high bounds of type or array index referenced
4390       --  by First, Last, or Length attribute for array, set by Set_Bounds.
4391
4392       CE_Node : Node_Id;
4393       --  Constraint error node used if we have an attribute reference has
4394       --  an argument that raises a constraint error. In this case we replace
4395       --  the attribute with a raise constraint_error node. This is important
4396       --  processing, since otherwise gigi might see an attribute which it is
4397       --  unprepared to deal with.
4398
4399       function Aft_Value return Nat;
4400       --  Computes Aft value for current attribute prefix (used by Aft itself
4401       --  and also by Width for computing the Width of a fixed point type).
4402
4403       procedure Check_Expressions;
4404       --  In case where the attribute is not foldable, the expressions, if
4405       --  any, of the attribute, are in a non-static context. This procedure
4406       --  performs the required additional checks.
4407
4408       function Compile_Time_Known_Bounds (Typ : Entity_Id) return Boolean;
4409       --  Determines if the given type has compile time known bounds. Note
4410       --  that we enter the case statement even in cases where the prefix
4411       --  type does NOT have known bounds, so it is important to guard any
4412       --  attempt to evaluate both bounds with a call to this function.
4413
4414       procedure Compile_Time_Known_Attribute (N : Node_Id; Val : Uint);
4415       --  This procedure is called when the attribute N has a non-static
4416       --  but compile time known value given by Val. It includes the
4417       --  necessary checks for out of range values.
4418
4419       procedure Float_Attribute_Universal_Integer
4420         (IEEES_Val : Int;
4421          IEEEL_Val : Int;
4422          IEEEX_Val : Int;
4423          VAXFF_Val : Int;
4424          VAXDF_Val : Int;
4425          VAXGF_Val : Int;
4426          AAMPS_Val : Int;
4427          AAMPL_Val : Int);
4428       --  This procedure evaluates a float attribute with no arguments that
4429       --  returns a universal integer result. The parameters give the values
4430       --  for the possible floating-point root types. See ttypef for details.
4431       --  The prefix type is a float type (and is thus not a generic type).
4432
4433       procedure Float_Attribute_Universal_Real
4434         (IEEES_Val : String;
4435          IEEEL_Val : String;
4436          IEEEX_Val : String;
4437          VAXFF_Val : String;
4438          VAXDF_Val : String;
4439          VAXGF_Val : String;
4440          AAMPS_Val : String;
4441          AAMPL_Val : String);
4442       --  This procedure evaluates a float attribute with no arguments that
4443       --  returns a universal real result. The parameters give the values
4444       --  required for the possible floating-point root types in string
4445       --  format as real literals with a possible leading minus sign.
4446       --  The prefix type is a float type (and is thus not a generic type).
4447
4448       function Fore_Value return Nat;
4449       --  Computes the Fore value for the current attribute prefix, which is
4450       --  known to be a static fixed-point type. Used by Fore and Width.
4451
4452       function Mantissa return Uint;
4453       --  Returns the Mantissa value for the prefix type
4454
4455       procedure Set_Bounds;
4456       --  Used for First, Last and Length attributes applied to an array or
4457       --  array subtype. Sets the variables Lo_Bound and Hi_Bound to the low
4458       --  and high bound expressions for the index referenced by the attribute
4459       --  designator (i.e. the first index if no expression is present, and
4460       --  the N'th index if the value N is present as an expression). Also
4461       --  used for First and Last of scalar types. Static is reset to False
4462       --  if the type or index type is not statically constrained.
4463
4464       function Statically_Denotes_Entity (N : Node_Id) return Boolean;
4465       --  Verify that the prefix of a potentially static array attribute
4466       --  satisfies the conditions of 4.9 (14).
4467
4468       ---------------
4469       -- Aft_Value --
4470       ---------------
4471
4472       function Aft_Value return Nat is
4473          Result    : Nat;
4474          Delta_Val : Ureal;
4475
4476       begin
4477          Result := 1;
4478          Delta_Val := Delta_Value (P_Type);
4479          while Delta_Val < Ureal_Tenth loop
4480             Delta_Val := Delta_Val * Ureal_10;
4481             Result := Result + 1;
4482          end loop;
4483
4484          return Result;
4485       end Aft_Value;
4486
4487       -----------------------
4488       -- Check_Expressions --
4489       -----------------------
4490
4491       procedure Check_Expressions is
4492          E : Node_Id;
4493       begin
4494          E := E1;
4495          while Present (E) loop
4496             Check_Non_Static_Context (E);
4497             Next (E);
4498          end loop;
4499       end Check_Expressions;
4500
4501       ----------------------------------
4502       -- Compile_Time_Known_Attribute --
4503       ----------------------------------
4504
4505       procedure Compile_Time_Known_Attribute (N : Node_Id; Val : Uint) is
4506          T : constant Entity_Id := Etype (N);
4507
4508       begin
4509          Fold_Uint (N, Val, False);
4510
4511          --  Check that result is in bounds of the type if it is static
4512
4513          if Is_In_Range (N, T) then
4514             null;
4515
4516          elsif Is_Out_Of_Range (N, T) then
4517             Apply_Compile_Time_Constraint_Error
4518               (N, "value not in range of}?", CE_Range_Check_Failed);
4519
4520          elsif not Range_Checks_Suppressed (T) then
4521             Enable_Range_Check (N);
4522
4523          else
4524             Set_Do_Range_Check (N, False);
4525          end if;
4526       end Compile_Time_Known_Attribute;
4527
4528       -------------------------------
4529       -- Compile_Time_Known_Bounds --
4530       -------------------------------
4531
4532       function Compile_Time_Known_Bounds (Typ : Entity_Id) return Boolean is
4533       begin
4534          return
4535            Compile_Time_Known_Value (Type_Low_Bound (Typ))
4536              and then
4537            Compile_Time_Known_Value (Type_High_Bound (Typ));
4538       end Compile_Time_Known_Bounds;
4539
4540       ---------------------------------------
4541       -- Float_Attribute_Universal_Integer --
4542       ---------------------------------------
4543
4544       procedure Float_Attribute_Universal_Integer
4545         (IEEES_Val : Int;
4546          IEEEL_Val : Int;
4547          IEEEX_Val : Int;
4548          VAXFF_Val : Int;
4549          VAXDF_Val : Int;
4550          VAXGF_Val : Int;
4551          AAMPS_Val : Int;
4552          AAMPL_Val : Int)
4553       is
4554          Val  : Int;
4555          Digs : constant Nat := UI_To_Int (Digits_Value (P_Base_Type));
4556
4557       begin
4558          if Vax_Float (P_Base_Type) then
4559             if Digs = VAXFF_Digits then
4560                Val := VAXFF_Val;
4561             elsif Digs = VAXDF_Digits then
4562                Val := VAXDF_Val;
4563             else pragma Assert (Digs = VAXGF_Digits);
4564                Val := VAXGF_Val;
4565             end if;
4566
4567          elsif Is_AAMP_Float (P_Base_Type) then
4568             if Digs = AAMPS_Digits then
4569                Val := AAMPS_Val;
4570             else pragma Assert (Digs = AAMPL_Digits);
4571                Val := AAMPL_Val;
4572             end if;
4573
4574          else
4575             if Digs = IEEES_Digits then
4576                Val := IEEES_Val;
4577             elsif Digs = IEEEL_Digits then
4578                Val := IEEEL_Val;
4579             else pragma Assert (Digs = IEEEX_Digits);
4580                Val := IEEEX_Val;
4581             end if;
4582          end if;
4583
4584          Fold_Uint (N, UI_From_Int (Val), True);
4585       end Float_Attribute_Universal_Integer;
4586
4587       ------------------------------------
4588       -- Float_Attribute_Universal_Real --
4589       ------------------------------------
4590
4591       procedure Float_Attribute_Universal_Real
4592         (IEEES_Val : String;
4593          IEEEL_Val : String;
4594          IEEEX_Val : String;
4595          VAXFF_Val : String;
4596          VAXDF_Val : String;
4597          VAXGF_Val : String;
4598          AAMPS_Val : String;
4599          AAMPL_Val : String)
4600       is
4601          Val  : Node_Id;
4602          Digs : constant Nat := UI_To_Int (Digits_Value (P_Base_Type));
4603
4604       begin
4605          if Vax_Float (P_Base_Type) then
4606             if Digs = VAXFF_Digits then
4607                Val := Real_Convert (VAXFF_Val);
4608             elsif Digs = VAXDF_Digits then
4609                Val := Real_Convert (VAXDF_Val);
4610             else pragma Assert (Digs = VAXGF_Digits);
4611                Val := Real_Convert (VAXGF_Val);
4612             end if;
4613
4614          elsif Is_AAMP_Float (P_Base_Type) then
4615             if Digs = AAMPS_Digits then
4616                Val := Real_Convert (AAMPS_Val);
4617             else pragma Assert (Digs = AAMPL_Digits);
4618                Val := Real_Convert (AAMPL_Val);
4619             end if;
4620
4621          else
4622             if Digs = IEEES_Digits then
4623                Val := Real_Convert (IEEES_Val);
4624             elsif Digs = IEEEL_Digits then
4625                Val := Real_Convert (IEEEL_Val);
4626             else pragma Assert (Digs = IEEEX_Digits);
4627                Val := Real_Convert (IEEEX_Val);
4628             end if;
4629          end if;
4630
4631          Set_Sloc (Val, Loc);
4632          Rewrite (N, Val);
4633          Set_Is_Static_Expression (N, Static);
4634          Analyze_And_Resolve (N, C_Type);
4635       end Float_Attribute_Universal_Real;
4636
4637       ----------------
4638       -- Fore_Value --
4639       ----------------
4640
4641       --  Note that the Fore calculation is based on the actual values
4642       --  of the bounds, and does not take into account possible rounding.
4643
4644       function Fore_Value return Nat is
4645          Lo      : constant Uint  := Expr_Value (Type_Low_Bound (P_Type));
4646          Hi      : constant Uint  := Expr_Value (Type_High_Bound (P_Type));
4647          Small   : constant Ureal := Small_Value (P_Type);
4648          Lo_Real : constant Ureal := Lo * Small;
4649          Hi_Real : constant Ureal := Hi * Small;
4650          T       : Ureal;
4651          R       : Nat;
4652
4653       begin
4654          --  Bounds are given in terms of small units, so first compute
4655          --  proper values as reals.
4656
4657          T := UR_Max (abs Lo_Real, abs Hi_Real);
4658          R := 2;
4659
4660          --  Loop to compute proper value if more than one digit required
4661
4662          while T >= Ureal_10 loop
4663             R := R + 1;
4664             T := T / Ureal_10;
4665          end loop;
4666
4667          return R;
4668       end Fore_Value;
4669
4670       --------------
4671       -- Mantissa --
4672       --------------
4673
4674       --  Table of mantissa values accessed by function  Computed using
4675       --  the relation:
4676
4677       --    T'Mantissa = integer next above (D * log(10)/log(2)) + 1)
4678
4679       --  where D is T'Digits (RM83 3.5.7)
4680
4681       Mantissa_Value : constant array (Nat range 1 .. 40) of Nat := (
4682           1 =>   5,
4683           2 =>   8,
4684           3 =>  11,
4685           4 =>  15,
4686           5 =>  18,
4687           6 =>  21,
4688           7 =>  25,
4689           8 =>  28,
4690           9 =>  31,
4691          10 =>  35,
4692          11 =>  38,
4693          12 =>  41,
4694          13 =>  45,
4695          14 =>  48,
4696          15 =>  51,
4697          16 =>  55,
4698          17 =>  58,
4699          18 =>  61,
4700          19 =>  65,
4701          20 =>  68,
4702          21 =>  71,
4703          22 =>  75,
4704          23 =>  78,
4705          24 =>  81,
4706          25 =>  85,
4707          26 =>  88,
4708          27 =>  91,
4709          28 =>  95,
4710          29 =>  98,
4711          30 => 101,
4712          31 => 104,
4713          32 => 108,
4714          33 => 111,
4715          34 => 114,
4716          35 => 118,
4717          36 => 121,
4718          37 => 124,
4719          38 => 128,
4720          39 => 131,
4721          40 => 134);
4722
4723       function Mantissa return Uint is
4724       begin
4725          return
4726            UI_From_Int (Mantissa_Value (UI_To_Int (Digits_Value (P_Type))));
4727       end Mantissa;
4728
4729       ----------------
4730       -- Set_Bounds --
4731       ----------------
4732
4733       procedure Set_Bounds is
4734          Ndim : Nat;
4735          Indx : Node_Id;
4736          Ityp : Entity_Id;
4737
4738       begin
4739          --  For a string literal subtype, we have to construct the bounds.
4740          --  Valid Ada code never applies attributes to string literals, but
4741          --  it is convenient to allow the expander to generate attribute
4742          --  references of this type (e.g. First and Last applied to a string
4743          --  literal).
4744
4745          --  Note that the whole point of the E_String_Literal_Subtype is to
4746          --  avoid this construction of bounds, but the cases in which we
4747          --  have to materialize them are rare enough that we don't worry!
4748
4749          --  The low bound is simply the low bound of the base type. The
4750          --  high bound is computed from the length of the string and this
4751          --  low bound.
4752
4753          if Ekind (P_Type) = E_String_Literal_Subtype then
4754             Ityp := Etype (First_Index (Base_Type (P_Type)));
4755             Lo_Bound := Type_Low_Bound (Ityp);
4756
4757             Hi_Bound :=
4758               Make_Integer_Literal (Sloc (P),
4759                 Intval =>
4760                   Expr_Value (Lo_Bound) + String_Literal_Length (P_Type) - 1);
4761
4762             Set_Parent (Hi_Bound, P);
4763             Analyze_And_Resolve (Hi_Bound, Etype (Lo_Bound));
4764             return;
4765
4766          --  For non-array case, just get bounds of scalar type
4767
4768          elsif Is_Scalar_Type (P_Type) then
4769             Ityp := P_Type;
4770
4771             --  For a fixed-point type, we must freeze to get the attributes
4772             --  of the fixed-point type set now so we can reference them.
4773
4774             if Is_Fixed_Point_Type (P_Type)
4775               and then not Is_Frozen (Base_Type (P_Type))
4776               and then Compile_Time_Known_Value (Type_Low_Bound (P_Type))
4777               and then Compile_Time_Known_Value (Type_High_Bound (P_Type))
4778             then
4779                Freeze_Fixed_Point_Type (Base_Type (P_Type));
4780             end if;
4781
4782          --  For array case, get type of proper index
4783
4784          else
4785             if No (E1) then
4786                Ndim := 1;
4787             else
4788                Ndim := UI_To_Int (Expr_Value (E1));
4789             end if;
4790
4791             Indx := First_Index (P_Type);
4792             for J in 1 .. Ndim - 1 loop
4793                Next_Index (Indx);
4794             end loop;
4795
4796             --  If no index type, get out (some other error occurred, and
4797             --  we don't have enough information to complete the job!)
4798
4799             if No (Indx) then
4800                Lo_Bound := Error;
4801                Hi_Bound := Error;
4802                return;
4803             end if;
4804
4805             Ityp := Etype (Indx);
4806          end if;
4807
4808          --  A discrete range in an index constraint is allowed to be a
4809          --  subtype indication. This is syntactically a pain, but should
4810          --  not propagate to the entity for the corresponding index subtype.
4811          --  After checking that the subtype indication is legal, the range
4812          --  of the subtype indication should be transfered to the entity.
4813          --  The attributes for the bounds should remain the simple retrievals
4814          --  that they are now.
4815
4816          Lo_Bound := Type_Low_Bound (Ityp);
4817          Hi_Bound := Type_High_Bound (Ityp);
4818
4819          if not Is_Static_Subtype (Ityp) then
4820             Static := False;
4821          end if;
4822       end Set_Bounds;
4823
4824       -------------------------------
4825       -- Statically_Denotes_Entity --
4826       -------------------------------
4827
4828       function Statically_Denotes_Entity (N : Node_Id) return Boolean is
4829          E : Entity_Id;
4830
4831       begin
4832          if not Is_Entity_Name (N) then
4833             return False;
4834          else
4835             E := Entity (N);
4836          end if;
4837
4838          return
4839            Nkind (Parent (E)) /= N_Object_Renaming_Declaration
4840              or else Statically_Denotes_Entity (Renamed_Object (E));
4841       end Statically_Denotes_Entity;
4842
4843    --  Start of processing for Eval_Attribute
4844
4845    begin
4846       --  Acquire first two expressions (at the moment, no attributes
4847       --  take more than two expressions in any case).
4848
4849       if Present (Expressions (N)) then
4850          E1 := First (Expressions (N));
4851          E2 := Next (E1);
4852       else
4853          E1 := Empty;
4854          E2 := Empty;
4855       end if;
4856
4857       --  Special processing for Enabled attribute. This attribute has a very
4858       --  special prefix, and the easiest way to avoid lots of special checks
4859       --  to protect this special prefix from causing trouble is to deal with
4860       --  this attribute immediately and be done with it.
4861
4862       if Id = Attribute_Enabled then
4863
4864          --  Evaluate the Enabled attribute
4865
4866          --  We skip evaluation if the expander is not active. This is not just
4867          --  an optimization. It is of key importance that we not rewrite the
4868          --  attribute in a generic template, since we want to pick up the
4869          --  setting of the check in the instance, and testing expander active
4870          --  is as easy way of doing this as any.
4871
4872          if Expander_Active then
4873             declare
4874                C : constant Check_Id := Get_Check_Id (Chars (P));
4875                R : Boolean;
4876
4877             begin
4878                if No (E1) then
4879                   if C in Predefined_Check_Id then
4880                      R := Scope_Suppress (C);
4881                   else
4882                      R := Is_Check_Suppressed (Empty, C);
4883                   end if;
4884
4885                else
4886                   R := Is_Check_Suppressed (Entity (E1), C);
4887                end if;
4888
4889                if R then
4890                   Rewrite (N, New_Occurrence_Of (Standard_False, Loc));
4891                else
4892                   Rewrite (N, New_Occurrence_Of (Standard_True, Loc));
4893                end if;
4894             end;
4895          end if;
4896
4897          return;
4898       end if;
4899
4900       --  Special processing for cases where the prefix is an object. For
4901       --  this purpose, a string literal counts as an object (attributes
4902       --  of string literals can only appear in generated code).
4903
4904       if Is_Object_Reference (P) or else Nkind (P) = N_String_Literal then
4905
4906          --  For Component_Size, the prefix is an array object, and we apply
4907          --  the attribute to the type of the object. This is allowed for
4908          --  both unconstrained and constrained arrays, since the bounds
4909          --  have no influence on the value of this attribute.
4910
4911          if Id = Attribute_Component_Size then
4912             P_Entity := Etype (P);
4913
4914          --  For First and Last, the prefix is an array object, and we apply
4915          --  the attribute to the type of the array, but we need a constrained
4916          --  type for this, so we use the actual subtype if available.
4917
4918          elsif Id = Attribute_First
4919                  or else
4920                Id = Attribute_Last
4921                  or else
4922                Id = Attribute_Length
4923          then
4924             declare
4925                AS : constant Entity_Id := Get_Actual_Subtype_If_Available (P);
4926
4927             begin
4928                if Present (AS) and then Is_Constrained (AS) then
4929                   P_Entity := AS;
4930
4931                --  If we have an unconstrained type, cannot fold
4932
4933                else
4934                   Check_Expressions;
4935                   return;
4936                end if;
4937             end;
4938
4939          --  For Size, give size of object if available, otherwise we
4940          --  cannot fold Size.
4941
4942          elsif Id = Attribute_Size then
4943             if Is_Entity_Name (P)
4944               and then Known_Esize (Entity (P))
4945             then
4946                Compile_Time_Known_Attribute (N, Esize (Entity (P)));
4947                return;
4948
4949             else
4950                Check_Expressions;
4951                return;
4952             end if;
4953
4954          --  For Alignment, give size of object if available, otherwise we
4955          --  cannot fold Alignment.
4956
4957          elsif Id = Attribute_Alignment then
4958             if Is_Entity_Name (P)
4959               and then Known_Alignment (Entity (P))
4960             then
4961                Fold_Uint (N, Alignment (Entity (P)), False);
4962                return;
4963
4964             else
4965                Check_Expressions;
4966                return;
4967             end if;
4968
4969          --  No other attributes for objects are folded
4970
4971          else
4972             Check_Expressions;
4973             return;
4974          end if;
4975
4976       --  Cases where P is not an object. Cannot do anything if P is
4977       --  not the name of an entity.
4978
4979       elsif not Is_Entity_Name (P) then
4980          Check_Expressions;
4981          return;
4982
4983       --  Otherwise get prefix entity
4984
4985       else
4986          P_Entity := Entity (P);
4987       end if;
4988
4989       --  At this stage P_Entity is the entity to which the attribute
4990       --  is to be applied. This is usually simply the entity of the
4991       --  prefix, except in some cases of attributes for objects, where
4992       --  as described above, we apply the attribute to the object type.
4993
4994       --  First foldable possibility is a scalar or array type (RM 4.9(7))
4995       --  that is not generic (generic types are eliminated by RM 4.9(25)).
4996       --  Note we allow non-static non-generic types at this stage as further
4997       --  described below.
4998
4999       if Is_Type (P_Entity)
5000         and then (Is_Scalar_Type (P_Entity) or Is_Array_Type (P_Entity))
5001         and then (not Is_Generic_Type (P_Entity))
5002       then
5003          P_Type := P_Entity;
5004
5005       --  Second foldable possibility is an array object (RM 4.9(8))
5006
5007       elsif (Ekind (P_Entity) = E_Variable
5008                or else
5009              Ekind (P_Entity) = E_Constant)
5010         and then Is_Array_Type (Etype (P_Entity))
5011         and then (not Is_Generic_Type (Etype (P_Entity)))
5012       then
5013          P_Type := Etype (P_Entity);
5014
5015          --  If the entity is an array constant with an unconstrained nominal
5016          --  subtype then get the type from the initial value. If the value has
5017          --  been expanded into assignments, there is no expression and the
5018          --  attribute reference remains dynamic.
5019          --  We could do better here and retrieve the type ???
5020
5021          if Ekind (P_Entity) = E_Constant
5022            and then not Is_Constrained (P_Type)
5023          then
5024             if No (Constant_Value (P_Entity)) then
5025                return;
5026             else
5027                P_Type := Etype (Constant_Value (P_Entity));
5028             end if;
5029          end if;
5030
5031       --  Definite must be folded if the prefix is not a generic type,
5032       --  that is to say if we are within an instantiation. Same processing
5033       --  applies to the GNAT attributes Has_Discriminants, Type_Class,
5034       --  and Unconstrained_Array.
5035
5036       elsif (Id = Attribute_Definite
5037                or else
5038              Id = Attribute_Has_Access_Values
5039                or else
5040              Id = Attribute_Has_Discriminants
5041                or else
5042              Id = Attribute_Type_Class
5043                or else
5044              Id = Attribute_Unconstrained_Array)
5045         and then not Is_Generic_Type (P_Entity)
5046       then
5047          P_Type := P_Entity;
5048
5049       --  We can fold 'Size applied to a type if the size is known
5050       --  (as happens for a size from an attribute definition clause).
5051       --  At this stage, this can happen only for types (e.g. record
5052       --  types) for which the size is always non-static. We exclude
5053       --  generic types from consideration (since they have bogus
5054       --  sizes set within templates).
5055
5056       elsif Id = Attribute_Size
5057         and then Is_Type (P_Entity)
5058         and then (not Is_Generic_Type (P_Entity))
5059         and then Known_Static_RM_Size (P_Entity)
5060       then
5061          Compile_Time_Known_Attribute (N, RM_Size (P_Entity));
5062          return;
5063
5064       --  We can fold 'Alignment applied to a type if the alignment is known
5065       --  (as happens for an alignment from an attribute definition clause).
5066       --  At this stage, this can happen only for types (e.g. record
5067       --  types) for which the size is always non-static. We exclude
5068       --  generic types from consideration (since they have bogus
5069       --  sizes set within templates).
5070
5071       elsif Id = Attribute_Alignment
5072         and then Is_Type (P_Entity)
5073         and then (not Is_Generic_Type (P_Entity))
5074         and then Known_Alignment (P_Entity)
5075       then
5076          Compile_Time_Known_Attribute (N, Alignment (P_Entity));
5077          return;
5078
5079       --  If this is an access attribute that is known to fail accessibility
5080       --  check, rewrite accordingly.
5081
5082       elsif Attribute_Name (N) = Name_Access
5083         and then Raises_Constraint_Error (N)
5084       then
5085          Rewrite (N,
5086            Make_Raise_Program_Error (Loc,
5087              Reason => PE_Accessibility_Check_Failed));
5088          Set_Etype (N, C_Type);
5089          return;
5090
5091       --  No other cases are foldable (they certainly aren't static, and at
5092       --  the moment we don't try to fold any cases other than these three).
5093
5094       else
5095          Check_Expressions;
5096          return;
5097       end if;
5098
5099       --  If either attribute or the prefix is Any_Type, then propagate
5100       --  Any_Type to the result and don't do anything else at all.
5101
5102       if P_Type = Any_Type
5103         or else (Present (E1) and then Etype (E1) = Any_Type)
5104         or else (Present (E2) and then Etype (E2) = Any_Type)
5105       then
5106          Set_Etype (N, Any_Type);
5107          return;
5108       end if;
5109
5110       --  Scalar subtype case. We have not yet enforced the static requirement
5111       --  of (RM 4.9(7)) and we don't intend to just yet, since there are cases
5112       --  of non-static attribute references (e.g. S'Digits for a non-static
5113       --  floating-point type, which we can compute at compile time).
5114
5115       --  Note: this folding of non-static attributes is not simply a case of
5116       --  optimization. For many of the attributes affected, Gigi cannot handle
5117       --  the attribute and depends on the front end having folded them away.
5118
5119       --  Note: although we don't require staticness at this stage, we do set
5120       --  the Static variable to record the staticness, for easy reference by
5121       --  those attributes where it matters (e.g. Succ and Pred), and also to
5122       --  be used to ensure that non-static folded things are not marked as
5123       --  being static (a check that is done right at the end).
5124
5125       P_Root_Type := Root_Type (P_Type);
5126       P_Base_Type := Base_Type (P_Type);
5127
5128       --  If the root type or base type is generic, then we cannot fold. This
5129       --  test is needed because subtypes of generic types are not always
5130       --  marked as being generic themselves (which seems odd???)
5131
5132       if Is_Generic_Type (P_Root_Type)
5133         or else Is_Generic_Type (P_Base_Type)
5134       then
5135          return;
5136       end if;
5137
5138       if Is_Scalar_Type (P_Type) then
5139          Static := Is_OK_Static_Subtype (P_Type);
5140
5141       --  Array case. We enforce the constrained requirement of (RM 4.9(7-8))
5142       --  since we can't do anything with unconstrained arrays. In addition,
5143       --  only the First, Last and Length attributes are possibly static.
5144
5145       --  Definite, Has_Access_Values, Has_Discriminants, Type_Class, and
5146       --  Unconstrained_Array are again exceptions, because they apply as
5147       --  well to unconstrained types.
5148
5149       --  In addition Component_Size is an exception since it is possibly
5150       --  foldable, even though it is never static, and it does apply to
5151       --  unconstrained arrays. Furthermore, it is essential to fold this
5152       --  in the packed case, since otherwise the value will be incorrect.
5153
5154       elsif Id = Attribute_Definite
5155               or else
5156             Id = Attribute_Has_Access_Values
5157               or else
5158             Id = Attribute_Has_Discriminants
5159               or else
5160             Id = Attribute_Type_Class
5161               or else
5162             Id = Attribute_Unconstrained_Array
5163               or else
5164             Id = Attribute_Component_Size
5165       then
5166          Static := False;
5167
5168       else
5169          if not Is_Constrained (P_Type)
5170            or else (Id /= Attribute_First and then
5171                     Id /= Attribute_Last  and then
5172                     Id /= Attribute_Length)
5173          then
5174             Check_Expressions;
5175             return;
5176          end if;
5177
5178          --  The rules in (RM 4.9(7,8)) require a static array, but as in the
5179          --  scalar case, we hold off on enforcing staticness, since there are
5180          --  cases which we can fold at compile time even though they are not
5181          --  static (e.g. 'Length applied to a static index, even though other
5182          --  non-static indexes make the array type non-static). This is only
5183          --  an optimization, but it falls out essentially free, so why not.
5184          --  Again we compute the variable Static for easy reference later
5185          --  (note that no array attributes are static in Ada 83).
5186
5187          Static := Ada_Version >= Ada_95
5188                      and then Statically_Denotes_Entity (P);
5189
5190          declare
5191             N : Node_Id;
5192
5193          begin
5194             N := First_Index (P_Type);
5195             while Present (N) loop
5196                Static := Static and then Is_Static_Subtype (Etype (N));
5197
5198                --  If however the index type is generic, attributes cannot
5199                --  be folded.
5200
5201                if Is_Generic_Type (Etype (N))
5202                  and then Id /= Attribute_Component_Size
5203                then
5204                   return;
5205                end if;
5206
5207                Next_Index (N);
5208             end loop;
5209          end;
5210       end if;
5211
5212       --  Check any expressions that are present. Note that these expressions,
5213       --  depending on the particular attribute type, are either part of the
5214       --  attribute designator, or they are arguments in a case where the
5215       --  attribute reference returns a function. In the latter case, the
5216       --  rule in (RM 4.9(22)) applies and in particular requires the type
5217       --  of the expressions to be scalar in order for the attribute to be
5218       --  considered to be static.
5219
5220       declare
5221          E : Node_Id;
5222
5223       begin
5224          E := E1;
5225          while Present (E) loop
5226
5227             --  If expression is not static, then the attribute reference
5228             --  result certainly cannot be static.
5229
5230             if not Is_Static_Expression (E) then
5231                Static := False;
5232             end if;
5233
5234             --  If the result is not known at compile time, or is not of
5235             --  a scalar type, then the result is definitely not static,
5236             --  so we can quit now.
5237
5238             if not Compile_Time_Known_Value (E)
5239               or else not Is_Scalar_Type (Etype (E))
5240             then
5241                --  An odd special case, if this is a Pos attribute, this
5242                --  is where we need to apply a range check since it does
5243                --  not get done anywhere else.
5244
5245                if Id = Attribute_Pos then
5246                   if Is_Integer_Type (Etype (E)) then
5247                      Apply_Range_Check (E, Etype (N));
5248                   end if;
5249                end if;
5250
5251                Check_Expressions;
5252                return;
5253
5254             --  If the expression raises a constraint error, then so does
5255             --  the attribute reference. We keep going in this case because
5256             --  we are still interested in whether the attribute reference
5257             --  is static even if it is not static.
5258
5259             elsif Raises_Constraint_Error (E) then
5260                Set_Raises_Constraint_Error (N);
5261             end if;
5262
5263             Next (E);
5264          end loop;
5265
5266          if Raises_Constraint_Error (Prefix (N)) then
5267             return;
5268          end if;
5269       end;
5270
5271       --  Deal with the case of a static attribute reference that raises
5272       --  constraint error. The Raises_Constraint_Error flag will already
5273       --  have been set, and the Static flag shows whether the attribute
5274       --  reference is static. In any case we certainly can't fold such an
5275       --  attribute reference.
5276
5277       --  Note that the rewriting of the attribute node with the constraint
5278       --  error node is essential in this case, because otherwise Gigi might
5279       --  blow up on one of the attributes it never expects to see.
5280
5281       --  The constraint_error node must have the type imposed by the context,
5282       --  to avoid spurious errors in the enclosing expression.
5283
5284       if Raises_Constraint_Error (N) then
5285          CE_Node :=
5286            Make_Raise_Constraint_Error (Sloc (N),
5287              Reason => CE_Range_Check_Failed);
5288          Set_Etype (CE_Node, Etype (N));
5289          Set_Raises_Constraint_Error (CE_Node);
5290          Check_Expressions;
5291          Rewrite (N, Relocate_Node (CE_Node));
5292          Set_Is_Static_Expression (N, Static);
5293          return;
5294       end if;
5295
5296       --  At this point we have a potentially foldable attribute reference.
5297       --  If Static is set, then the attribute reference definitely obeys
5298       --  the requirements in (RM 4.9(7,8,22)), and it definitely can be
5299       --  folded. If Static is not set, then the attribute may or may not
5300       --  be foldable, and the individual attribute processing routines
5301       --  test Static as required in cases where it makes a difference.
5302
5303       --  In the case where Static is not set, we do know that all the
5304       --  expressions present are at least known at compile time (we
5305       --  assumed above that if this was not the case, then there was
5306       --  no hope of static evaluation). However, we did not require
5307       --  that the bounds of the prefix type be compile time known,
5308       --  let alone static). That's because there are many attributes
5309       --  that can be computed at compile time on non-static subtypes,
5310       --  even though such references are not static expressions.
5311
5312       case Id is
5313
5314       --------------
5315       -- Adjacent --
5316       --------------
5317
5318       when Attribute_Adjacent =>
5319          Fold_Ureal (N,
5320            Eval_Fat.Adjacent
5321              (P_Root_Type, Expr_Value_R (E1), Expr_Value_R (E2)), Static);
5322
5323       ---------
5324       -- Aft --
5325       ---------
5326
5327       when Attribute_Aft =>
5328          Fold_Uint (N, UI_From_Int (Aft_Value), True);
5329
5330       ---------------
5331       -- Alignment --
5332       ---------------
5333
5334       when Attribute_Alignment => Alignment_Block : declare
5335          P_TypeA : constant Entity_Id := Underlying_Type (P_Type);
5336
5337       begin
5338          --  Fold if alignment is set and not otherwise
5339
5340          if Known_Alignment (P_TypeA) then
5341             Fold_Uint (N, Alignment (P_TypeA), Is_Discrete_Type (P_TypeA));
5342          end if;
5343       end Alignment_Block;
5344
5345       ---------------
5346       -- AST_Entry --
5347       ---------------
5348
5349       --  Can only be folded in No_Ast_Handler case
5350
5351       when Attribute_AST_Entry =>
5352          if not Is_AST_Entry (P_Entity) then
5353             Rewrite (N,
5354               New_Occurrence_Of (RTE (RE_No_AST_Handler), Loc));
5355          else
5356             null;
5357          end if;
5358
5359       ---------
5360       -- Bit --
5361       ---------
5362
5363       --  Bit can never be folded
5364
5365       when Attribute_Bit =>
5366          null;
5367
5368       ------------------
5369       -- Body_Version --
5370       ------------------
5371
5372       --  Body_version can never be static
5373
5374       when Attribute_Body_Version =>
5375          null;
5376
5377       -------------
5378       -- Ceiling --
5379       -------------
5380
5381       when Attribute_Ceiling =>
5382          Fold_Ureal (N,
5383            Eval_Fat.Ceiling (P_Root_Type, Expr_Value_R (E1)), Static);
5384
5385       --------------------
5386       -- Component_Size --
5387       --------------------
5388
5389       when Attribute_Component_Size =>
5390          if Known_Static_Component_Size (P_Type) then
5391             Fold_Uint (N, Component_Size (P_Type), False);
5392          end if;
5393
5394       -------------
5395       -- Compose --
5396       -------------
5397
5398       when Attribute_Compose =>
5399          Fold_Ureal (N,
5400            Eval_Fat.Compose
5401              (P_Root_Type, Expr_Value_R (E1), Expr_Value (E2)),
5402               Static);
5403
5404       -----------------
5405       -- Constrained --
5406       -----------------
5407
5408       --  Constrained is never folded for now, there may be cases that
5409       --  could be handled at compile time. to be looked at later.
5410
5411       when Attribute_Constrained =>
5412          null;
5413
5414       ---------------
5415       -- Copy_Sign --
5416       ---------------
5417
5418       when Attribute_Copy_Sign =>
5419          Fold_Ureal (N,
5420            Eval_Fat.Copy_Sign
5421              (P_Root_Type, Expr_Value_R (E1), Expr_Value_R (E2)), Static);
5422
5423       -----------
5424       -- Delta --
5425       -----------
5426
5427       when Attribute_Delta =>
5428          Fold_Ureal (N, Delta_Value (P_Type), True);
5429
5430       --------------
5431       -- Definite --
5432       --------------
5433
5434       when Attribute_Definite =>
5435          Rewrite (N, New_Occurrence_Of (
5436            Boolean_Literals (not Is_Indefinite_Subtype (P_Entity)), Loc));
5437          Analyze_And_Resolve (N, Standard_Boolean);
5438
5439       ------------
5440       -- Denorm --
5441       ------------
5442
5443       when Attribute_Denorm =>
5444          Fold_Uint
5445            (N, UI_From_Int (Boolean'Pos (Denorm_On_Target)), True);
5446
5447       ------------
5448       -- Digits --
5449       ------------
5450
5451       when Attribute_Digits =>
5452          Fold_Uint (N, Digits_Value (P_Type), True);
5453
5454       ----------
5455       -- Emax --
5456       ----------
5457
5458       when Attribute_Emax =>
5459
5460          --  Ada 83 attribute is defined as (RM83 3.5.8)
5461
5462          --    T'Emax = 4 * T'Mantissa
5463
5464          Fold_Uint (N, 4 * Mantissa, True);
5465
5466       --------------
5467       -- Enum_Rep --
5468       --------------
5469
5470       when Attribute_Enum_Rep =>
5471
5472          --  For an enumeration type with a non-standard representation use
5473          --  the Enumeration_Rep field of the proper constant. Note that this
5474          --  will not work for types Character/Wide_[Wide-]Character, since no
5475          --  real entities are created for the enumeration literals, but that
5476          --  does not matter since these two types do not have non-standard
5477          --  representations anyway.
5478
5479          if Is_Enumeration_Type (P_Type)
5480            and then Has_Non_Standard_Rep (P_Type)
5481          then
5482             Fold_Uint (N, Enumeration_Rep (Expr_Value_E (E1)), Static);
5483
5484          --  For enumeration types with standard representations and all
5485          --  other cases (i.e. all integer and modular types), Enum_Rep
5486          --  is equivalent to Pos.
5487
5488          else
5489             Fold_Uint (N, Expr_Value (E1), Static);
5490          end if;
5491
5492       -------------
5493       -- Epsilon --
5494       -------------
5495
5496       when Attribute_Epsilon =>
5497
5498          --  Ada 83 attribute is defined as (RM83 3.5.8)
5499
5500          --    T'Epsilon = 2.0**(1 - T'Mantissa)
5501
5502          Fold_Ureal (N, Ureal_2 ** (1 - Mantissa), True);
5503
5504       --------------
5505       -- Exponent --
5506       --------------
5507
5508       when Attribute_Exponent =>
5509          Fold_Uint (N,
5510            Eval_Fat.Exponent (P_Root_Type, Expr_Value_R (E1)), Static);
5511
5512       -----------
5513       -- First --
5514       -----------
5515
5516       when Attribute_First => First_Attr :
5517       begin
5518          Set_Bounds;
5519
5520          if Compile_Time_Known_Value (Lo_Bound) then
5521             if Is_Real_Type (P_Type) then
5522                Fold_Ureal (N, Expr_Value_R (Lo_Bound), Static);
5523             else
5524                Fold_Uint  (N, Expr_Value (Lo_Bound), Static);
5525             end if;
5526          end if;
5527       end First_Attr;
5528
5529       -----------------
5530       -- Fixed_Value --
5531       -----------------
5532
5533       when Attribute_Fixed_Value =>
5534          null;
5535
5536       -----------
5537       -- Floor --
5538       -----------
5539
5540       when Attribute_Floor =>
5541          Fold_Ureal (N,
5542            Eval_Fat.Floor (P_Root_Type, Expr_Value_R (E1)), Static);
5543
5544       ----------
5545       -- Fore --
5546       ----------
5547
5548       when Attribute_Fore =>
5549          if Compile_Time_Known_Bounds (P_Type) then
5550             Fold_Uint (N, UI_From_Int (Fore_Value), Static);
5551          end if;
5552
5553       --------------
5554       -- Fraction --
5555       --------------
5556
5557       when Attribute_Fraction =>
5558          Fold_Ureal (N,
5559            Eval_Fat.Fraction (P_Root_Type, Expr_Value_R (E1)), Static);
5560
5561       -----------------------
5562       -- Has_Access_Values --
5563       -----------------------
5564
5565       when Attribute_Has_Access_Values =>
5566          Rewrite (N, New_Occurrence_Of
5567            (Boolean_Literals (Has_Access_Values (P_Root_Type)), Loc));
5568          Analyze_And_Resolve (N, Standard_Boolean);
5569
5570       -----------------------
5571       -- Has_Discriminants --
5572       -----------------------
5573
5574       when Attribute_Has_Discriminants =>
5575          Rewrite (N, New_Occurrence_Of (
5576            Boolean_Literals (Has_Discriminants (P_Entity)), Loc));
5577          Analyze_And_Resolve (N, Standard_Boolean);
5578
5579       --------------
5580       -- Identity --
5581       --------------
5582
5583       when Attribute_Identity =>
5584          null;
5585
5586       -----------
5587       -- Image --
5588       -----------
5589
5590       --  Image is a scalar attribute, but is never static, because it is
5591       --  not a static function (having a non-scalar argument (RM 4.9(22))
5592       --  However, we can constant-fold the image of an enumeration literal
5593       --  if names are available.
5594
5595       when Attribute_Image =>
5596          if Is_Entity_Name (E1)
5597            and then Ekind (Entity (E1)) = E_Enumeration_Literal
5598            and then not Discard_Names (First_Subtype (Etype (E1)))
5599            and then not Global_Discard_Names
5600          then
5601             declare
5602                Lit : constant Entity_Id := Entity (E1);
5603                Str : String_Id;
5604             begin
5605                Start_String;
5606                Get_Unqualified_Decoded_Name_String (Chars (Lit));
5607                Set_Casing (All_Upper_Case);
5608                Store_String_Chars (Name_Buffer (1 .. Name_Len));
5609                Str := End_String;
5610                Rewrite (N, Make_String_Literal (Loc, Strval => Str));
5611                Analyze_And_Resolve (N, Standard_String);
5612                Set_Is_Static_Expression (N, False);
5613             end;
5614          end if;
5615
5616       ---------
5617       -- Img --
5618       ---------
5619
5620       --  Img is a scalar attribute, but is never static, because it is
5621       --  not a static function (having a non-scalar argument (RM 4.9(22))
5622
5623       when Attribute_Img =>
5624          null;
5625
5626       -------------------
5627       -- Integer_Value --
5628       -------------------
5629
5630       when Attribute_Integer_Value =>
5631          null;
5632
5633       -----------
5634       -- Large --
5635       -----------
5636
5637       when Attribute_Large =>
5638
5639          --  For fixed-point, we use the identity:
5640
5641          --    T'Large = (2.0**T'Mantissa - 1.0) * T'Small
5642
5643          if Is_Fixed_Point_Type (P_Type) then
5644             Rewrite (N,
5645               Make_Op_Multiply (Loc,
5646                 Left_Opnd =>
5647                   Make_Op_Subtract (Loc,
5648                     Left_Opnd =>
5649                       Make_Op_Expon (Loc,
5650                         Left_Opnd =>
5651                           Make_Real_Literal (Loc, Ureal_2),
5652                         Right_Opnd =>
5653                           Make_Attribute_Reference (Loc,
5654                             Prefix => P,
5655                             Attribute_Name => Name_Mantissa)),
5656                     Right_Opnd => Make_Real_Literal (Loc, Ureal_1)),
5657
5658                 Right_Opnd =>
5659                   Make_Real_Literal (Loc, Small_Value (Entity (P)))));
5660
5661             Analyze_And_Resolve (N, C_Type);
5662
5663          --  Floating-point (Ada 83 compatibility)
5664
5665          else
5666             --  Ada 83 attribute is defined as (RM83 3.5.8)
5667
5668             --    T'Large = 2.0**T'Emax * (1.0 - 2.0**(-T'Mantissa))
5669
5670             --  where
5671
5672             --    T'Emax = 4 * T'Mantissa
5673
5674             Fold_Ureal (N,
5675               Ureal_2 ** (4 * Mantissa) * (Ureal_1 - Ureal_2 ** (-Mantissa)),
5676               True);
5677          end if;
5678
5679       ----------
5680       -- Last --
5681       ----------
5682
5683       when Attribute_Last => Last :
5684       begin
5685          Set_Bounds;
5686
5687          if Compile_Time_Known_Value (Hi_Bound) then
5688             if Is_Real_Type (P_Type) then
5689                Fold_Ureal (N, Expr_Value_R (Hi_Bound), Static);
5690             else
5691                Fold_Uint  (N, Expr_Value (Hi_Bound), Static);
5692             end if;
5693          end if;
5694       end Last;
5695
5696       ------------------
5697       -- Leading_Part --
5698       ------------------
5699
5700       when Attribute_Leading_Part =>
5701          Fold_Ureal (N,
5702            Eval_Fat.Leading_Part
5703              (P_Root_Type, Expr_Value_R (E1), Expr_Value (E2)), Static);
5704
5705       ------------
5706       -- Length --
5707       ------------
5708
5709       when Attribute_Length => Length : declare
5710          Ind : Node_Id;
5711
5712       begin
5713          --  In the case of a generic index type, the bounds may
5714          --  appear static but the computation is not meaningful,
5715          --  and may generate a spurious warning.
5716
5717          Ind := First_Index (P_Type);
5718
5719          while Present (Ind) loop
5720             if Is_Generic_Type (Etype (Ind)) then
5721                return;
5722             end if;
5723
5724             Next_Index (Ind);
5725          end loop;
5726
5727          Set_Bounds;
5728
5729          if Compile_Time_Known_Value (Lo_Bound)
5730            and then Compile_Time_Known_Value (Hi_Bound)
5731          then
5732             Fold_Uint (N,
5733               UI_Max (0, 1 + (Expr_Value (Hi_Bound) - Expr_Value (Lo_Bound))),
5734               True);
5735          end if;
5736       end Length;
5737
5738       -------------
5739       -- Machine --
5740       -------------
5741
5742       when Attribute_Machine =>
5743          Fold_Ureal (N,
5744            Eval_Fat.Machine
5745              (P_Root_Type, Expr_Value_R (E1), Eval_Fat.Round, N),
5746            Static);
5747
5748       ------------------
5749       -- Machine_Emax --
5750       ------------------
5751
5752       when Attribute_Machine_Emax =>
5753          Float_Attribute_Universal_Integer (
5754            IEEES_Machine_Emax,
5755            IEEEL_Machine_Emax,
5756            IEEEX_Machine_Emax,
5757            VAXFF_Machine_Emax,
5758            VAXDF_Machine_Emax,
5759            VAXGF_Machine_Emax,
5760            AAMPS_Machine_Emax,
5761            AAMPL_Machine_Emax);
5762
5763       ------------------
5764       -- Machine_Emin --
5765       ------------------
5766
5767       when Attribute_Machine_Emin =>
5768          Float_Attribute_Universal_Integer (
5769            IEEES_Machine_Emin,
5770            IEEEL_Machine_Emin,
5771            IEEEX_Machine_Emin,
5772            VAXFF_Machine_Emin,
5773            VAXDF_Machine_Emin,
5774            VAXGF_Machine_Emin,
5775            AAMPS_Machine_Emin,
5776            AAMPL_Machine_Emin);
5777
5778       ----------------------
5779       -- Machine_Mantissa --
5780       ----------------------
5781
5782       when Attribute_Machine_Mantissa =>
5783          Float_Attribute_Universal_Integer (
5784            IEEES_Machine_Mantissa,
5785            IEEEL_Machine_Mantissa,
5786            IEEEX_Machine_Mantissa,
5787            VAXFF_Machine_Mantissa,
5788            VAXDF_Machine_Mantissa,
5789            VAXGF_Machine_Mantissa,
5790            AAMPS_Machine_Mantissa,
5791            AAMPL_Machine_Mantissa);
5792
5793       -----------------------
5794       -- Machine_Overflows --
5795       -----------------------
5796
5797       when Attribute_Machine_Overflows =>
5798
5799          --  Always true for fixed-point
5800
5801          if Is_Fixed_Point_Type (P_Type) then
5802             Fold_Uint (N, True_Value, True);
5803
5804          --  Floating point case
5805
5806          else
5807             Fold_Uint (N,
5808               UI_From_Int (Boolean'Pos (Machine_Overflows_On_Target)),
5809               True);
5810          end if;
5811
5812       -------------------
5813       -- Machine_Radix --
5814       -------------------
5815
5816       when Attribute_Machine_Radix =>
5817          if Is_Fixed_Point_Type (P_Type) then
5818             if Is_Decimal_Fixed_Point_Type (P_Type)
5819               and then Machine_Radix_10 (P_Type)
5820             then
5821                Fold_Uint (N, Uint_10, True);
5822             else
5823                Fold_Uint (N, Uint_2, True);
5824             end if;
5825
5826          --  All floating-point type always have radix 2
5827
5828          else
5829             Fold_Uint (N, Uint_2, True);
5830          end if;
5831
5832       ----------------------
5833       -- Machine_Rounding --
5834       ----------------------
5835
5836       --  Note: for the folding case, it is fine to treat Machine_Rounding
5837       --  exactly the same way as Rounding, since this is one of the allowed
5838       --  behaviors, and performance is not an issue here. It might be a bit
5839       --  better to give the same result as it would give at run-time, even
5840       --  though the non-determinism is certainly permitted.
5841
5842       when Attribute_Machine_Rounding =>
5843          Fold_Ureal (N,
5844            Eval_Fat.Rounding (P_Root_Type, Expr_Value_R (E1)), Static);
5845
5846       --------------------
5847       -- Machine_Rounds --
5848       --------------------
5849
5850       when Attribute_Machine_Rounds =>
5851
5852          --  Always False for fixed-point
5853
5854          if Is_Fixed_Point_Type (P_Type) then
5855             Fold_Uint (N, False_Value, True);
5856
5857          --  Else yield proper floating-point result
5858
5859          else
5860             Fold_Uint
5861               (N, UI_From_Int (Boolean'Pos (Machine_Rounds_On_Target)), True);
5862          end if;
5863
5864       ------------------
5865       -- Machine_Size --
5866       ------------------
5867
5868       --  Note: Machine_Size is identical to Object_Size
5869
5870       when Attribute_Machine_Size => Machine_Size : declare
5871          P_TypeA : constant Entity_Id := Underlying_Type (P_Type);
5872
5873       begin
5874          if Known_Esize (P_TypeA) then
5875             Fold_Uint (N, Esize (P_TypeA), True);
5876          end if;
5877       end Machine_Size;
5878
5879       --------------
5880       -- Mantissa --
5881       --------------
5882
5883       when Attribute_Mantissa =>
5884
5885          --  Fixed-point mantissa
5886
5887          if Is_Fixed_Point_Type (P_Type) then
5888
5889             --  Compile time foldable case
5890
5891             if Compile_Time_Known_Value (Type_Low_Bound  (P_Type))
5892                  and then
5893                Compile_Time_Known_Value (Type_High_Bound (P_Type))
5894             then
5895                --  The calculation of the obsolete Ada 83 attribute Mantissa
5896                --  is annoying, because of AI00143, quoted here:
5897
5898                --  !question 84-01-10
5899
5900                --  Consider the model numbers for F:
5901
5902                --         type F is delta 1.0 range -7.0 .. 8.0;
5903
5904                --  The wording requires that F'MANTISSA be the SMALLEST
5905                --  integer number for which each  bound  of the specified
5906                --  range is either a model number or lies at most small
5907                --  distant from a model number. This means F'MANTISSA
5908                --  is required to be 3 since the range  -7.0 .. 7.0 fits
5909                --  in 3 signed bits, and 8 is "at most" 1.0 from a model
5910                --  number, namely, 7. Is this analysis correct? Note that
5911                --  this implies the upper bound of the range is not
5912                --  represented as a model number.
5913
5914                --  !response 84-03-17
5915
5916                --  The analysis is correct. The upper and lower bounds for
5917                --  a fixed  point type can lie outside the range of model
5918                --  numbers.
5919
5920                declare
5921                   Siz     : Uint;
5922                   LBound  : Ureal;
5923                   UBound  : Ureal;
5924                   Bound   : Ureal;
5925                   Max_Man : Uint;
5926
5927                begin
5928                   LBound  := Expr_Value_R (Type_Low_Bound  (P_Type));
5929                   UBound  := Expr_Value_R (Type_High_Bound (P_Type));
5930                   Bound   := UR_Max (UR_Abs (LBound), UR_Abs (UBound));
5931                   Max_Man := UR_Trunc (Bound / Small_Value (P_Type));
5932
5933                   --  If the Bound is exactly a model number, i.e. a multiple
5934                   --  of Small, then we back it off by one to get the integer
5935                   --  value that must be representable.
5936
5937                   if Small_Value (P_Type) * Max_Man = Bound then
5938                      Max_Man := Max_Man - 1;
5939                   end if;
5940
5941                   --  Now find corresponding size = Mantissa value
5942
5943                   Siz := Uint_0;
5944                   while 2 ** Siz < Max_Man loop
5945                      Siz := Siz + 1;
5946                   end loop;
5947
5948                   Fold_Uint (N, Siz, True);
5949                end;
5950
5951             else
5952                --  The case of dynamic bounds cannot be evaluated at compile
5953                --  time. Instead we use a runtime routine (see Exp_Attr).
5954
5955                null;
5956             end if;
5957
5958          --  Floating-point Mantissa
5959
5960          else
5961             Fold_Uint (N, Mantissa, True);
5962          end if;
5963
5964       ---------
5965       -- Max --
5966       ---------
5967
5968       when Attribute_Max => Max :
5969       begin
5970          if Is_Real_Type (P_Type) then
5971             Fold_Ureal
5972               (N, UR_Max (Expr_Value_R (E1), Expr_Value_R (E2)), Static);
5973          else
5974             Fold_Uint (N, UI_Max (Expr_Value (E1), Expr_Value (E2)), Static);
5975          end if;
5976       end Max;
5977
5978       ----------------------------------
5979       -- Max_Size_In_Storage_Elements --
5980       ----------------------------------
5981
5982       --  Max_Size_In_Storage_Elements is simply the Size rounded up to a
5983       --  Storage_Unit boundary. We can fold any cases for which the size
5984       --  is known by the front end.
5985
5986       when Attribute_Max_Size_In_Storage_Elements =>
5987          if Known_Esize (P_Type) then
5988             Fold_Uint (N,
5989               (Esize (P_Type) + System_Storage_Unit - 1) /
5990                                           System_Storage_Unit,
5991                Static);
5992          end if;
5993
5994       --------------------
5995       -- Mechanism_Code --
5996       --------------------
5997
5998       when Attribute_Mechanism_Code =>
5999          declare
6000             Val    : Int;
6001             Formal : Entity_Id;
6002             Mech   : Mechanism_Type;
6003
6004          begin
6005             if No (E1) then
6006                Mech := Mechanism (P_Entity);
6007
6008             else
6009                Val := UI_To_Int (Expr_Value (E1));
6010
6011                Formal := First_Formal (P_Entity);
6012                for J in 1 .. Val - 1 loop
6013                   Next_Formal (Formal);
6014                end loop;
6015                Mech := Mechanism (Formal);
6016             end if;
6017
6018             if Mech < 0 then
6019                Fold_Uint (N, UI_From_Int (Int (-Mech)), True);
6020             end if;
6021          end;
6022
6023       ---------
6024       -- Min --
6025       ---------
6026
6027       when Attribute_Min => Min :
6028       begin
6029          if Is_Real_Type (P_Type) then
6030             Fold_Ureal
6031               (N, UR_Min (Expr_Value_R (E1), Expr_Value_R (E2)), Static);
6032          else
6033             Fold_Uint
6034               (N, UI_Min (Expr_Value (E1), Expr_Value (E2)), Static);
6035          end if;
6036       end Min;
6037
6038       ---------
6039       -- Mod --
6040       ---------
6041
6042       when Attribute_Mod =>
6043          Fold_Uint
6044            (N, UI_Mod (Expr_Value (E1), Modulus (P_Base_Type)), Static);
6045
6046       -----------
6047       -- Model --
6048       -----------
6049
6050       when Attribute_Model =>
6051          Fold_Ureal (N,
6052            Eval_Fat.Model (P_Root_Type, Expr_Value_R (E1)), Static);
6053
6054       ----------------
6055       -- Model_Emin --
6056       ----------------
6057
6058       when Attribute_Model_Emin =>
6059          Float_Attribute_Universal_Integer (
6060            IEEES_Model_Emin,
6061            IEEEL_Model_Emin,
6062            IEEEX_Model_Emin,
6063            VAXFF_Model_Emin,
6064            VAXDF_Model_Emin,
6065            VAXGF_Model_Emin,
6066            AAMPS_Model_Emin,
6067            AAMPL_Model_Emin);
6068
6069       -------------------
6070       -- Model_Epsilon --
6071       -------------------
6072
6073       when Attribute_Model_Epsilon =>
6074          Float_Attribute_Universal_Real (
6075            IEEES_Model_Epsilon'Universal_Literal_String,
6076            IEEEL_Model_Epsilon'Universal_Literal_String,
6077            IEEEX_Model_Epsilon'Universal_Literal_String,
6078            VAXFF_Model_Epsilon'Universal_Literal_String,
6079            VAXDF_Model_Epsilon'Universal_Literal_String,
6080            VAXGF_Model_Epsilon'Universal_Literal_String,
6081            AAMPS_Model_Epsilon'Universal_Literal_String,
6082            AAMPL_Model_Epsilon'Universal_Literal_String);
6083
6084       --------------------
6085       -- Model_Mantissa --
6086       --------------------
6087
6088       when Attribute_Model_Mantissa =>
6089          Float_Attribute_Universal_Integer (
6090            IEEES_Model_Mantissa,
6091            IEEEL_Model_Mantissa,
6092            IEEEX_Model_Mantissa,
6093            VAXFF_Model_Mantissa,
6094            VAXDF_Model_Mantissa,
6095            VAXGF_Model_Mantissa,
6096            AAMPS_Model_Mantissa,
6097            AAMPL_Model_Mantissa);
6098
6099       -----------------
6100       -- Model_Small --
6101       -----------------
6102
6103       when Attribute_Model_Small =>
6104          Float_Attribute_Universal_Real (
6105            IEEES_Model_Small'Universal_Literal_String,
6106            IEEEL_Model_Small'Universal_Literal_String,
6107            IEEEX_Model_Small'Universal_Literal_String,
6108            VAXFF_Model_Small'Universal_Literal_String,
6109            VAXDF_Model_Small'Universal_Literal_String,
6110            VAXGF_Model_Small'Universal_Literal_String,
6111            AAMPS_Model_Small'Universal_Literal_String,
6112            AAMPL_Model_Small'Universal_Literal_String);
6113
6114       -------------
6115       -- Modulus --
6116       -------------
6117
6118       when Attribute_Modulus =>
6119          Fold_Uint (N, Modulus (P_Type), True);
6120
6121       --------------------
6122       -- Null_Parameter --
6123       --------------------
6124
6125       --  Cannot fold, we know the value sort of, but the whole point is
6126       --  that there is no way to talk about this imaginary value except
6127       --  by using the attribute, so we leave it the way it is.
6128
6129       when Attribute_Null_Parameter =>
6130          null;
6131
6132       -----------------
6133       -- Object_Size --
6134       -----------------
6135
6136       --  The Object_Size attribute for a type returns the Esize of the
6137       --  type and can be folded if this value is known.
6138
6139       when Attribute_Object_Size => Object_Size : declare
6140          P_TypeA : constant Entity_Id := Underlying_Type (P_Type);
6141
6142       begin
6143          if Known_Esize (P_TypeA) then
6144             Fold_Uint (N, Esize (P_TypeA), True);
6145          end if;
6146       end Object_Size;
6147
6148       -------------------------
6149       -- Passed_By_Reference --
6150       -------------------------
6151
6152       --  Scalar types are never passed by reference
6153
6154       when Attribute_Passed_By_Reference =>
6155          Fold_Uint (N, False_Value, True);
6156
6157       ---------
6158       -- Pos --
6159       ---------
6160
6161       when Attribute_Pos =>
6162          Fold_Uint (N, Expr_Value (E1), True);
6163
6164       ----------
6165       -- Pred --
6166       ----------
6167
6168       when Attribute_Pred => Pred :
6169       begin
6170          --  Floating-point case
6171
6172          if Is_Floating_Point_Type (P_Type) then
6173             Fold_Ureal (N,
6174               Eval_Fat.Pred (P_Root_Type, Expr_Value_R (E1)), Static);
6175
6176          --  Fixed-point case
6177
6178          elsif Is_Fixed_Point_Type (P_Type) then
6179             Fold_Ureal (N,
6180               Expr_Value_R (E1) - Small_Value (P_Type), True);
6181
6182          --  Modular integer case (wraps)
6183
6184          elsif Is_Modular_Integer_Type (P_Type) then
6185             Fold_Uint (N, (Expr_Value (E1) - 1) mod Modulus (P_Type), Static);
6186
6187          --  Other scalar cases
6188
6189          else
6190             pragma Assert (Is_Scalar_Type (P_Type));
6191
6192             if Is_Enumeration_Type (P_Type)
6193               and then Expr_Value (E1) =
6194                          Expr_Value (Type_Low_Bound (P_Base_Type))
6195             then
6196                Apply_Compile_Time_Constraint_Error
6197                  (N, "Pred of `&''First`",
6198                   CE_Overflow_Check_Failed,
6199                   Ent  => P_Base_Type,
6200                   Warn => not Static);
6201
6202                Check_Expressions;
6203                return;
6204             end if;
6205
6206             Fold_Uint (N, Expr_Value (E1) - 1, Static);
6207          end if;
6208       end Pred;
6209
6210       -----------
6211       -- Range --
6212       -----------
6213
6214       --  No processing required, because by this stage, Range has been
6215       --  replaced by First .. Last, so this branch can never be taken.
6216
6217       when Attribute_Range =>
6218          raise Program_Error;
6219
6220       ------------------
6221       -- Range_Length --
6222       ------------------
6223
6224       when Attribute_Range_Length =>
6225          Set_Bounds;
6226
6227          if Compile_Time_Known_Value (Hi_Bound)
6228            and then Compile_Time_Known_Value (Lo_Bound)
6229          then
6230             Fold_Uint (N,
6231               UI_Max
6232                 (0, Expr_Value (Hi_Bound) - Expr_Value (Lo_Bound) + 1),
6233                  Static);
6234          end if;
6235
6236       ---------------
6237       -- Remainder --
6238       ---------------
6239
6240       when Attribute_Remainder => Remainder : declare
6241          X : constant Ureal := Expr_Value_R (E1);
6242          Y : constant Ureal := Expr_Value_R (E2);
6243
6244       begin
6245          if UR_Is_Zero (Y) then
6246             Apply_Compile_Time_Constraint_Error
6247               (N, "division by zero in Remainder",
6248                CE_Overflow_Check_Failed,
6249                Warn => not Static);
6250
6251             Check_Expressions;
6252             return;
6253          end if;
6254
6255          Fold_Ureal (N, Eval_Fat.Remainder (P_Root_Type, X, Y), Static);
6256       end Remainder;
6257
6258       -----------
6259       -- Round --
6260       -----------
6261
6262       when Attribute_Round => Round :
6263       declare
6264          Sr : Ureal;
6265          Si : Uint;
6266
6267       begin
6268          --  First we get the (exact result) in units of small
6269
6270          Sr := Expr_Value_R (E1) / Small_Value (C_Type);
6271
6272          --  Now round that exactly to an integer
6273
6274          Si := UR_To_Uint (Sr);
6275
6276          --  Finally the result is obtained by converting back to real
6277
6278          Fold_Ureal (N, Si * Small_Value (C_Type), Static);
6279       end Round;
6280
6281       --------------
6282       -- Rounding --
6283       --------------
6284
6285       when Attribute_Rounding =>
6286          Fold_Ureal (N,
6287            Eval_Fat.Rounding (P_Root_Type, Expr_Value_R (E1)), Static);
6288
6289       ---------------
6290       -- Safe_Emax --
6291       ---------------
6292
6293       when Attribute_Safe_Emax =>
6294          Float_Attribute_Universal_Integer (
6295            IEEES_Safe_Emax,
6296            IEEEL_Safe_Emax,
6297            IEEEX_Safe_Emax,
6298            VAXFF_Safe_Emax,
6299            VAXDF_Safe_Emax,
6300            VAXGF_Safe_Emax,
6301            AAMPS_Safe_Emax,
6302            AAMPL_Safe_Emax);
6303
6304       ----------------
6305       -- Safe_First --
6306       ----------------
6307
6308       when Attribute_Safe_First =>
6309          Float_Attribute_Universal_Real (
6310            IEEES_Safe_First'Universal_Literal_String,
6311            IEEEL_Safe_First'Universal_Literal_String,
6312            IEEEX_Safe_First'Universal_Literal_String,
6313            VAXFF_Safe_First'Universal_Literal_String,
6314            VAXDF_Safe_First'Universal_Literal_String,
6315            VAXGF_Safe_First'Universal_Literal_String,
6316            AAMPS_Safe_First'Universal_Literal_String,
6317            AAMPL_Safe_First'Universal_Literal_String);
6318
6319       ----------------
6320       -- Safe_Large --
6321       ----------------
6322
6323       when Attribute_Safe_Large =>
6324          if Is_Fixed_Point_Type (P_Type) then
6325             Fold_Ureal
6326               (N, Expr_Value_R (Type_High_Bound (P_Base_Type)), Static);
6327          else
6328             Float_Attribute_Universal_Real (
6329               IEEES_Safe_Large'Universal_Literal_String,
6330               IEEEL_Safe_Large'Universal_Literal_String,
6331               IEEEX_Safe_Large'Universal_Literal_String,
6332               VAXFF_Safe_Large'Universal_Literal_String,
6333               VAXDF_Safe_Large'Universal_Literal_String,
6334               VAXGF_Safe_Large'Universal_Literal_String,
6335               AAMPS_Safe_Large'Universal_Literal_String,
6336               AAMPL_Safe_Large'Universal_Literal_String);
6337          end if;
6338
6339       ---------------
6340       -- Safe_Last --
6341       ---------------
6342
6343       when Attribute_Safe_Last =>
6344          Float_Attribute_Universal_Real (
6345            IEEES_Safe_Last'Universal_Literal_String,
6346            IEEEL_Safe_Last'Universal_Literal_String,
6347            IEEEX_Safe_Last'Universal_Literal_String,
6348            VAXFF_Safe_Last'Universal_Literal_String,
6349            VAXDF_Safe_Last'Universal_Literal_String,
6350            VAXGF_Safe_Last'Universal_Literal_String,
6351            AAMPS_Safe_Last'Universal_Literal_String,
6352            AAMPL_Safe_Last'Universal_Literal_String);
6353
6354       ----------------
6355       -- Safe_Small --
6356       ----------------
6357
6358       when Attribute_Safe_Small =>
6359
6360          --  In Ada 95, the old Ada 83 attribute Safe_Small is redundant
6361          --  for fixed-point, since is the same as Small, but we implement
6362          --  it for backwards compatibility.
6363
6364          if Is_Fixed_Point_Type (P_Type) then
6365             Fold_Ureal (N, Small_Value (P_Type), Static);
6366
6367          --  Ada 83 Safe_Small for floating-point cases
6368
6369          else
6370             Float_Attribute_Universal_Real (
6371               IEEES_Safe_Small'Universal_Literal_String,
6372               IEEEL_Safe_Small'Universal_Literal_String,
6373               IEEEX_Safe_Small'Universal_Literal_String,
6374               VAXFF_Safe_Small'Universal_Literal_String,
6375               VAXDF_Safe_Small'Universal_Literal_String,
6376               VAXGF_Safe_Small'Universal_Literal_String,
6377               AAMPS_Safe_Small'Universal_Literal_String,
6378               AAMPL_Safe_Small'Universal_Literal_String);
6379          end if;
6380
6381       -----------
6382       -- Scale --
6383       -----------
6384
6385       when Attribute_Scale =>
6386          Fold_Uint (N, Scale_Value (P_Type), True);
6387
6388       -------------
6389       -- Scaling --
6390       -------------
6391
6392       when Attribute_Scaling =>
6393          Fold_Ureal (N,
6394            Eval_Fat.Scaling
6395              (P_Root_Type, Expr_Value_R (E1), Expr_Value (E2)), Static);
6396
6397       ------------------
6398       -- Signed_Zeros --
6399       ------------------
6400
6401       when Attribute_Signed_Zeros =>
6402          Fold_Uint
6403            (N, UI_From_Int (Boolean'Pos (Signed_Zeros_On_Target)), Static);
6404
6405       ----------
6406       -- Size --
6407       ----------
6408
6409       --  Size attribute returns the RM size. All scalar types can be folded,
6410       --  as well as any types for which the size is known by the front end,
6411       --  including any type for which a size attribute is specified.
6412
6413       when Attribute_Size | Attribute_VADS_Size => Size : declare
6414          P_TypeA : constant Entity_Id := Underlying_Type (P_Type);
6415
6416       begin
6417          if RM_Size (P_TypeA) /= Uint_0 then
6418
6419             --  VADS_Size case
6420
6421             if Id = Attribute_VADS_Size or else Use_VADS_Size then
6422                declare
6423                   S : constant Node_Id := Size_Clause (P_TypeA);
6424
6425                begin
6426                   --  If a size clause applies, then use the size from it.
6427                   --  This is one of the rare cases where we can use the
6428                   --  Size_Clause field for a subtype when Has_Size_Clause
6429                   --  is False. Consider:
6430
6431                   --    type x is range 1 .. 64;
6432                   --    for x'size use 12;
6433                   --    subtype y is x range 0 .. 3;
6434
6435                   --  Here y has a size clause inherited from x, but normally
6436                   --  it does not apply, and y'size is 2. However, y'VADS_Size
6437                   --  is indeed 12 and not 2.
6438
6439                   if Present (S)
6440                     and then Is_OK_Static_Expression (Expression (S))
6441                   then
6442                      Fold_Uint (N, Expr_Value (Expression (S)), True);
6443
6444                   --  If no size is specified, then we simply use the object
6445                   --  size in the VADS_Size case (e.g. Natural'Size is equal
6446                   --  to Integer'Size, not one less).
6447
6448                   else
6449                      Fold_Uint (N, Esize (P_TypeA), True);
6450                   end if;
6451                end;
6452
6453             --  Normal case (Size) in which case we want the RM_Size
6454
6455             else
6456                Fold_Uint (N,
6457                  RM_Size (P_TypeA),
6458                  Static and then Is_Discrete_Type (P_TypeA));
6459             end if;
6460          end if;
6461       end Size;
6462
6463       -----------
6464       -- Small --
6465       -----------
6466
6467       when Attribute_Small =>
6468
6469          --  The floating-point case is present only for Ada 83 compatability.
6470          --  Note that strictly this is an illegal addition, since we are
6471          --  extending an Ada 95 defined attribute, but we anticipate an
6472          --  ARG ruling that will permit this.
6473
6474          if Is_Floating_Point_Type (P_Type) then
6475
6476             --  Ada 83 attribute is defined as (RM83 3.5.8)
6477
6478             --    T'Small = 2.0**(-T'Emax - 1)
6479
6480             --  where
6481
6482             --    T'Emax = 4 * T'Mantissa
6483
6484             Fold_Ureal (N, Ureal_2 ** ((-(4 * Mantissa)) - 1), Static);
6485
6486          --  Normal Ada 95 fixed-point case
6487
6488          else
6489             Fold_Ureal (N, Small_Value (P_Type), True);
6490          end if;
6491
6492       -----------------
6493       -- Stream_Size --
6494       -----------------
6495
6496       when Attribute_Stream_Size =>
6497          null;
6498
6499       ----------
6500       -- Succ --
6501       ----------
6502
6503       when Attribute_Succ => Succ :
6504       begin
6505          --  Floating-point case
6506
6507          if Is_Floating_Point_Type (P_Type) then
6508             Fold_Ureal (N,
6509               Eval_Fat.Succ (P_Root_Type, Expr_Value_R (E1)), Static);
6510
6511          --  Fixed-point case
6512
6513          elsif Is_Fixed_Point_Type (P_Type) then
6514             Fold_Ureal (N,
6515               Expr_Value_R (E1) + Small_Value (P_Type), Static);
6516
6517          --  Modular integer case (wraps)
6518
6519          elsif Is_Modular_Integer_Type (P_Type) then
6520             Fold_Uint (N, (Expr_Value (E1) + 1) mod Modulus (P_Type), Static);
6521
6522          --  Other scalar cases
6523
6524          else
6525             pragma Assert (Is_Scalar_Type (P_Type));
6526
6527             if Is_Enumeration_Type (P_Type)
6528               and then Expr_Value (E1) =
6529                          Expr_Value (Type_High_Bound (P_Base_Type))
6530             then
6531                Apply_Compile_Time_Constraint_Error
6532                  (N, "Succ of `&''Last`",
6533                   CE_Overflow_Check_Failed,
6534                   Ent  => P_Base_Type,
6535                   Warn => not Static);
6536
6537                Check_Expressions;
6538                return;
6539             else
6540                Fold_Uint (N, Expr_Value (E1) + 1, Static);
6541             end if;
6542          end if;
6543       end Succ;
6544
6545       ----------------
6546       -- Truncation --
6547       ----------------
6548
6549       when Attribute_Truncation =>
6550          Fold_Ureal (N,
6551            Eval_Fat.Truncation (P_Root_Type, Expr_Value_R (E1)), Static);
6552
6553       ----------------
6554       -- Type_Class --
6555       ----------------
6556
6557       when Attribute_Type_Class => Type_Class : declare
6558          Typ : constant Entity_Id := Underlying_Type (P_Base_Type);
6559          Id  : RE_Id;
6560
6561       begin
6562          if Is_Descendent_Of_Address (Typ) then
6563             Id := RE_Type_Class_Address;
6564
6565          elsif Is_Enumeration_Type (Typ) then
6566             Id := RE_Type_Class_Enumeration;
6567
6568          elsif Is_Integer_Type (Typ) then
6569             Id := RE_Type_Class_Integer;
6570
6571          elsif Is_Fixed_Point_Type (Typ) then
6572             Id := RE_Type_Class_Fixed_Point;
6573
6574          elsif Is_Floating_Point_Type (Typ) then
6575             Id := RE_Type_Class_Floating_Point;
6576
6577          elsif Is_Array_Type (Typ) then
6578             Id := RE_Type_Class_Array;
6579
6580          elsif Is_Record_Type (Typ) then
6581             Id := RE_Type_Class_Record;
6582
6583          elsif Is_Access_Type (Typ) then
6584             Id := RE_Type_Class_Access;
6585
6586          elsif Is_Enumeration_Type (Typ) then
6587             Id := RE_Type_Class_Enumeration;
6588
6589          elsif Is_Task_Type (Typ) then
6590             Id := RE_Type_Class_Task;
6591
6592          --  We treat protected types like task types. It would make more
6593          --  sense to have another enumeration value, but after all the
6594          --  whole point of this feature is to be exactly DEC compatible,
6595          --  and changing the type Type_Clas would not meet this requirement.
6596
6597          elsif Is_Protected_Type (Typ) then
6598             Id := RE_Type_Class_Task;
6599
6600          --  Not clear if there are any other possibilities, but if there
6601          --  are, then we will treat them as the address case.
6602
6603          else
6604             Id := RE_Type_Class_Address;
6605          end if;
6606
6607          Rewrite (N, New_Occurrence_Of (RTE (Id), Loc));
6608       end Type_Class;
6609
6610       -----------------------
6611       -- Unbiased_Rounding --
6612       -----------------------
6613
6614       when Attribute_Unbiased_Rounding =>
6615          Fold_Ureal (N,
6616            Eval_Fat.Unbiased_Rounding (P_Root_Type, Expr_Value_R (E1)),
6617            Static);
6618
6619       -------------------------
6620       -- Unconstrained_Array --
6621       -------------------------
6622
6623       when Attribute_Unconstrained_Array => Unconstrained_Array : declare
6624          Typ : constant Entity_Id := Underlying_Type (P_Type);
6625
6626       begin
6627          Rewrite (N, New_Occurrence_Of (
6628            Boolean_Literals (
6629              Is_Array_Type (P_Type)
6630               and then not Is_Constrained (Typ)), Loc));
6631
6632          --  Analyze and resolve as boolean, note that this attribute is
6633          --  a static attribute in GNAT.
6634
6635          Analyze_And_Resolve (N, Standard_Boolean);
6636          Static := True;
6637       end Unconstrained_Array;
6638
6639       ---------------
6640       -- VADS_Size --
6641       ---------------
6642
6643       --  Processing is shared with Size
6644
6645       ---------
6646       -- Val --
6647       ---------
6648
6649       when Attribute_Val => Val :
6650       begin
6651          if  Expr_Value (E1) < Expr_Value (Type_Low_Bound (P_Base_Type))
6652            or else
6653              Expr_Value (E1) > Expr_Value (Type_High_Bound (P_Base_Type))
6654          then
6655             Apply_Compile_Time_Constraint_Error
6656               (N, "Val expression out of range",
6657                CE_Range_Check_Failed,
6658                Warn => not Static);
6659
6660             Check_Expressions;
6661             return;
6662
6663          else
6664             Fold_Uint (N, Expr_Value (E1), Static);
6665          end if;
6666       end Val;
6667
6668       ----------------
6669       -- Value_Size --
6670       ----------------
6671
6672       --  The Value_Size attribute for a type returns the RM size of the
6673       --  type. This an always be folded for scalar types, and can also
6674       --  be folded for non-scalar types if the size is set.
6675
6676       when Attribute_Value_Size => Value_Size : declare
6677          P_TypeA : constant Entity_Id := Underlying_Type (P_Type);
6678       begin
6679          if RM_Size (P_TypeA) /= Uint_0 then
6680             Fold_Uint (N, RM_Size (P_TypeA), True);
6681          end if;
6682       end Value_Size;
6683
6684       -------------
6685       -- Version --
6686       -------------
6687
6688       --  Version can never be static
6689
6690       when Attribute_Version =>
6691          null;
6692
6693       ----------------
6694       -- Wide_Image --
6695       ----------------
6696
6697       --  Wide_Image is a scalar attribute, but is never static, because it
6698       --  is not a static function (having a non-scalar argument (RM 4.9(22))
6699
6700       when Attribute_Wide_Image =>
6701          null;
6702
6703       ---------------------
6704       -- Wide_Wide_Image --
6705       ---------------------
6706
6707       --  Wide_Wide_Image is a scalar attribute but is never static, because it
6708       --  is not a static function (having a non-scalar argument (RM 4.9(22)).
6709
6710       when Attribute_Wide_Wide_Image =>
6711          null;
6712
6713       ---------------------
6714       -- Wide_Wide_Width --
6715       ---------------------
6716
6717       --  Processing for Wide_Wide_Width is combined with Width
6718
6719       ----------------
6720       -- Wide_Width --
6721       ----------------
6722
6723       --  Processing for Wide_Width is combined with Width
6724
6725       -----------
6726       -- Width --
6727       -----------
6728
6729       --  This processing also handles the case of Wide_[Wide_]Width
6730
6731       when Attribute_Width |
6732            Attribute_Wide_Width |
6733            Attribute_Wide_Wide_Width => Width :
6734       begin
6735          if Compile_Time_Known_Bounds (P_Type) then
6736
6737             --  Floating-point types
6738
6739             if Is_Floating_Point_Type (P_Type) then
6740
6741                --  Width is zero for a null range (RM 3.5 (38))
6742
6743                if Expr_Value_R (Type_High_Bound (P_Type)) <
6744                   Expr_Value_R (Type_Low_Bound (P_Type))
6745                then
6746                   Fold_Uint (N, Uint_0, True);
6747
6748                else
6749                   --  For floating-point, we have +N.dddE+nnn where length
6750                   --  of ddd is determined by type'Digits - 1, but is one
6751                   --  if Digits is one (RM 3.5 (33)).
6752
6753                   --  nnn is set to 2 for Short_Float and Float (32 bit
6754                   --  floats), and 3 for Long_Float and Long_Long_Float.
6755                   --  For machines where Long_Long_Float is the IEEE
6756                   --  extended precision type, the exponent takes 4 digits.
6757
6758                   declare
6759                      Len : Int :=
6760                              Int'Max (2, UI_To_Int (Digits_Value (P_Type)));
6761
6762                   begin
6763                      if Esize (P_Type) <= 32 then
6764                         Len := Len + 6;
6765                      elsif Esize (P_Type) = 64 then
6766                         Len := Len + 7;
6767                      else
6768                         Len := Len + 8;
6769                      end if;
6770
6771                      Fold_Uint (N, UI_From_Int (Len), True);
6772                   end;
6773                end if;
6774
6775             --  Fixed-point types
6776
6777             elsif Is_Fixed_Point_Type (P_Type) then
6778
6779                --  Width is zero for a null range (RM 3.5 (38))
6780
6781                if Expr_Value (Type_High_Bound (P_Type)) <
6782                   Expr_Value (Type_Low_Bound  (P_Type))
6783                then
6784                   Fold_Uint (N, Uint_0, True);
6785
6786                --  The non-null case depends on the specific real type
6787
6788                else
6789                   --  For fixed-point type width is Fore + 1 + Aft (RM 3.5(34))
6790
6791                   Fold_Uint
6792                     (N, UI_From_Int (Fore_Value + 1 + Aft_Value), True);
6793                end if;
6794
6795             --  Discrete types
6796
6797             else
6798                declare
6799                   R  : constant Entity_Id := Root_Type (P_Type);
6800                   Lo : constant Uint :=
6801                          Expr_Value (Type_Low_Bound (P_Type));
6802                   Hi : constant Uint :=
6803                          Expr_Value (Type_High_Bound (P_Type));
6804                   W  : Nat;
6805                   Wt : Nat;
6806                   T  : Uint;
6807                   L  : Node_Id;
6808                   C  : Character;
6809
6810                begin
6811                   --  Empty ranges
6812
6813                   if Lo > Hi then
6814                      W := 0;
6815
6816                   --  Width for types derived from Standard.Character
6817                   --  and Standard.Wide_[Wide_]Character.
6818
6819                   elsif R = Standard_Character
6820                      or else R = Standard_Wide_Character
6821                      or else R = Standard_Wide_Wide_Character
6822                   then
6823                      W := 0;
6824
6825                      --  Set W larger if needed
6826
6827                      for J in UI_To_Int (Lo) .. UI_To_Int (Hi) loop
6828
6829                         --  All wide characters look like Hex_hhhhhhhh
6830
6831                         if J > 255 then
6832                            W := 12;
6833
6834                         else
6835                            C := Character'Val (J);
6836
6837                            --  Test for all cases where Character'Image
6838                            --  yields an image that is longer than three
6839                            --  characters. First the cases of Reserved_xxx
6840                            --  names (length = 12).
6841
6842                            case C is
6843                               when Reserved_128 | Reserved_129 |
6844                                    Reserved_132 | Reserved_153
6845
6846                                 => Wt := 12;
6847
6848                               when BS | HT | LF | VT | FF | CR |
6849                                    SO | SI | EM | FS | GS | RS |
6850                                    US | RI | MW | ST | PM
6851
6852                                 => Wt := 2;
6853
6854                               when NUL | SOH | STX | ETX | EOT |
6855                                    ENQ | ACK | BEL | DLE | DC1 |
6856                                    DC2 | DC3 | DC4 | NAK | SYN |
6857                                    ETB | CAN | SUB | ESC | DEL |
6858                                    BPH | NBH | NEL | SSA | ESA |
6859                                    HTS | HTJ | VTS | PLD | PLU |
6860                                    SS2 | SS3 | DCS | PU1 | PU2 |
6861                                    STS | CCH | SPA | EPA | SOS |
6862                                    SCI | CSI | OSC | APC
6863
6864                                 => Wt := 3;
6865
6866                               when Space .. Tilde |
6867                                    No_Break_Space .. LC_Y_Diaeresis
6868
6869                                 => Wt := 3;
6870                            end case;
6871
6872                            W := Int'Max (W, Wt);
6873                         end if;
6874                      end loop;
6875
6876                   --  Width for types derived from Standard.Boolean
6877
6878                   elsif R = Standard_Boolean then
6879                      if Lo = 0 then
6880                         W := 5; -- FALSE
6881                      else
6882                         W := 4; -- TRUE
6883                      end if;
6884
6885                   --  Width for integer types
6886
6887                   elsif Is_Integer_Type (P_Type) then
6888                      T := UI_Max (abs Lo, abs Hi);
6889
6890                      W := 2;
6891                      while T >= 10 loop
6892                         W := W + 1;
6893                         T := T / 10;
6894                      end loop;
6895
6896                   --  Only remaining possibility is user declared enum type
6897
6898                   else
6899                      pragma Assert (Is_Enumeration_Type (P_Type));
6900
6901                      W := 0;
6902                      L := First_Literal (P_Type);
6903
6904                      while Present (L) loop
6905
6906                         --  Only pay attention to in range characters
6907
6908                         if Lo <= Enumeration_Pos (L)
6909                           and then Enumeration_Pos (L) <= Hi
6910                         then
6911                            --  For Width case, use decoded name
6912
6913                            if Id = Attribute_Width then
6914                               Get_Decoded_Name_String (Chars (L));
6915                               Wt := Nat (Name_Len);
6916
6917                            --  For Wide_[Wide_]Width, use encoded name, and
6918                            --  then adjust for the encoding.
6919
6920                            else
6921                               Get_Name_String (Chars (L));
6922
6923                               --  Character literals are always of length 3
6924
6925                               if Name_Buffer (1) = 'Q' then
6926                                  Wt := 3;
6927
6928                               --  Otherwise loop to adjust for upper/wide chars
6929
6930                               else
6931                                  Wt := Nat (Name_Len);
6932
6933                                  for J in 1 .. Name_Len loop
6934                                     if Name_Buffer (J) = 'U' then
6935                                        Wt := Wt - 2;
6936                                     elsif Name_Buffer (J) = 'W' then
6937                                        Wt := Wt - 4;
6938                                     end if;
6939                                  end loop;
6940                               end if;
6941                            end if;
6942
6943                            W := Int'Max (W, Wt);
6944                         end if;
6945
6946                         Next_Literal (L);
6947                      end loop;
6948                   end if;
6949
6950                   Fold_Uint (N, UI_From_Int (W), True);
6951                end;
6952             end if;
6953          end if;
6954       end Width;
6955
6956       --  The following attributes can never be folded, and furthermore we
6957       --  should not even have entered the case statement for any of these.
6958       --  Note that in some cases, the values have already been folded as
6959       --  a result of the processing in Analyze_Attribute.
6960
6961       when Attribute_Abort_Signal             |
6962            Attribute_Access                   |
6963            Attribute_Address                  |
6964            Attribute_Address_Size             |
6965            Attribute_Asm_Input                |
6966            Attribute_Asm_Output               |
6967            Attribute_Base                     |
6968            Attribute_Bit_Order                |
6969            Attribute_Bit_Position             |
6970            Attribute_Callable                 |
6971            Attribute_Caller                   |
6972            Attribute_Class                    |
6973            Attribute_Code_Address             |
6974            Attribute_Count                    |
6975            Attribute_Default_Bit_Order        |
6976            Attribute_Elaborated               |
6977            Attribute_Elab_Body                |
6978            Attribute_Elab_Spec                |
6979            Attribute_Enabled                  |
6980            Attribute_External_Tag             |
6981            Attribute_First_Bit                |
6982            Attribute_Input                    |
6983            Attribute_Last_Bit                 |
6984            Attribute_Maximum_Alignment        |
6985            Attribute_Output                   |
6986            Attribute_Partition_ID             |
6987            Attribute_Pool_Address             |
6988            Attribute_Position                 |
6989            Attribute_Priority                 |
6990            Attribute_Read                     |
6991            Attribute_Storage_Pool             |
6992            Attribute_Storage_Size             |
6993            Attribute_Storage_Unit             |
6994            Attribute_Stub_Type                |
6995            Attribute_Tag                      |
6996            Attribute_Target_Name              |
6997            Attribute_Terminated               |
6998            Attribute_To_Address               |
6999            Attribute_UET_Address              |
7000            Attribute_Unchecked_Access         |
7001            Attribute_Universal_Literal_String |
7002            Attribute_Unrestricted_Access      |
7003            Attribute_Valid                    |
7004            Attribute_Value                    |
7005            Attribute_Wchar_T_Size             |
7006            Attribute_Wide_Value               |
7007            Attribute_Wide_Wide_Value          |
7008            Attribute_Word_Size                |
7009            Attribute_Write                    =>
7010
7011          raise Program_Error;
7012       end case;
7013
7014       --  At the end of the case, one more check. If we did a static evaluation
7015       --  so that the result is now a literal, then set Is_Static_Expression
7016       --  in the constant only if the prefix type is a static subtype. For
7017       --  non-static subtypes, the folding is still OK, but not static.
7018
7019       --  An exception is the GNAT attribute Constrained_Array which is
7020       --  defined to be a static attribute in all cases.
7021
7022       if Nkind (N) = N_Integer_Literal
7023         or else Nkind (N) = N_Real_Literal
7024         or else Nkind (N) = N_Character_Literal
7025         or else Nkind (N) = N_String_Literal
7026         or else (Is_Entity_Name (N)
7027                   and then Ekind (Entity (N)) = E_Enumeration_Literal)
7028       then
7029          Set_Is_Static_Expression (N, Static);
7030
7031       --  If this is still an attribute reference, then it has not been folded
7032       --  and that means that its expressions are in a non-static context.
7033
7034       elsif Nkind (N) = N_Attribute_Reference then
7035          Check_Expressions;
7036
7037       --  Note: the else case not covered here are odd cases where the
7038       --  processing has transformed the attribute into something other
7039       --  than a constant. Nothing more to do in such cases.
7040
7041       else
7042          null;
7043       end if;
7044    end Eval_Attribute;
7045
7046    ------------------------------
7047    -- Is_Anonymous_Tagged_Base --
7048    ------------------------------
7049
7050    function Is_Anonymous_Tagged_Base
7051      (Anon : Entity_Id;
7052       Typ  : Entity_Id)
7053       return Boolean
7054    is
7055    begin
7056       return
7057         Anon = Current_Scope
7058           and then Is_Itype (Anon)
7059           and then Associated_Node_For_Itype (Anon) = Parent (Typ);
7060    end Is_Anonymous_Tagged_Base;
7061
7062    --------------------------------
7063    -- Name_Implies_Lvalue_Prefix --
7064    --------------------------------
7065
7066    function Name_Implies_Lvalue_Prefix (Nam : Name_Id) return Boolean is
7067       pragma Assert (Is_Attribute_Name (Nam));
7068    begin
7069       return Attribute_Name_Implies_Lvalue_Prefix (Get_Attribute_Id (Nam));
7070    end Name_Implies_Lvalue_Prefix;
7071
7072    -----------------------
7073    -- Resolve_Attribute --
7074    -----------------------
7075
7076    procedure Resolve_Attribute (N : Node_Id; Typ : Entity_Id) is
7077       Loc      : constant Source_Ptr   := Sloc (N);
7078       P        : constant Node_Id      := Prefix (N);
7079       Aname    : constant Name_Id      := Attribute_Name (N);
7080       Attr_Id  : constant Attribute_Id := Get_Attribute_Id (Aname);
7081       Btyp     : constant Entity_Id    := Base_Type (Typ);
7082       Des_Btyp : Entity_Id;
7083       Index    : Interp_Index;
7084       It       : Interp;
7085       Nom_Subt : Entity_Id;
7086
7087       procedure Accessibility_Message;
7088       --  Error, or warning within an instance, if the static accessibility
7089       --  rules of 3.10.2 are violated.
7090
7091       ---------------------------
7092       -- Accessibility_Message --
7093       ---------------------------
7094
7095       procedure Accessibility_Message is
7096          Indic : Node_Id := Parent (Parent (N));
7097
7098       begin
7099          --  In an instance, this is a runtime check, but one we
7100          --  know will fail, so generate an appropriate warning.
7101
7102          if In_Instance_Body then
7103             Error_Msg_F
7104               ("?non-local pointer cannot point to local object", P);
7105             Error_Msg_F
7106               ("\?Program_Error will be raised at run time", P);
7107             Rewrite (N,
7108               Make_Raise_Program_Error (Loc,
7109                 Reason => PE_Accessibility_Check_Failed));
7110             Set_Etype (N, Typ);
7111             return;
7112
7113          else
7114             Error_Msg_F
7115               ("non-local pointer cannot point to local object", P);
7116
7117             --  Check for case where we have a missing access definition
7118
7119             if Is_Record_Type (Current_Scope)
7120               and then
7121                 (Nkind (Parent (N)) = N_Discriminant_Association
7122                    or else
7123                  Nkind (Parent (N)) = N_Index_Or_Discriminant_Constraint)
7124             then
7125                Indic := Parent (Parent (N));
7126                while Present (Indic)
7127                  and then Nkind (Indic) /= N_Subtype_Indication
7128                loop
7129                   Indic := Parent (Indic);
7130                end loop;
7131
7132                if Present (Indic) then
7133                   Error_Msg_NE
7134                     ("\use an access definition for" &
7135                      " the access discriminant of&",
7136                      N, Entity (Subtype_Mark (Indic)));
7137                end if;
7138             end if;
7139          end if;
7140       end Accessibility_Message;
7141
7142    --  Start of processing for Resolve_Attribute
7143
7144    begin
7145       --  If error during analysis, no point in continuing, except for
7146       --  array types, where we get  better recovery by using unconstrained
7147       --  indices than nothing at all (see Check_Array_Type).
7148
7149       if Error_Posted (N)
7150         and then Attr_Id /= Attribute_First
7151         and then Attr_Id /= Attribute_Last
7152         and then Attr_Id /= Attribute_Length
7153         and then Attr_Id /= Attribute_Range
7154       then
7155          return;
7156       end if;
7157
7158       --  If attribute was universal type, reset to actual type
7159
7160       if Etype (N) = Universal_Integer
7161         or else Etype (N) = Universal_Real
7162       then
7163          Set_Etype (N, Typ);
7164       end if;
7165
7166       --  Remaining processing depends on attribute
7167
7168       case Attr_Id is
7169
7170          ------------
7171          -- Access --
7172          ------------
7173
7174          --  For access attributes, if the prefix denotes an entity, it is
7175          --  interpreted as a name, never as a call. It may be overloaded,
7176          --  in which case resolution uses the profile of the context type.
7177          --  Otherwise prefix must be resolved.
7178
7179          when Attribute_Access
7180             | Attribute_Unchecked_Access
7181             | Attribute_Unrestricted_Access =>
7182
7183          Access_Attribute : begin
7184             if Is_Variable (P) then
7185                Note_Possible_Modification (P);
7186             end if;
7187
7188             if Is_Entity_Name (P) then
7189                if Is_Overloaded (P) then
7190                   Get_First_Interp (P, Index, It);
7191                   while Present (It.Nam) loop
7192                      if Type_Conformant (Designated_Type (Typ), It.Nam) then
7193                         Set_Entity (P, It.Nam);
7194
7195                         --  The prefix is definitely NOT overloaded anymore at
7196                         --  this point, so we reset the Is_Overloaded flag to
7197                         --  avoid any confusion when reanalyzing the node.
7198
7199                         Set_Is_Overloaded (P, False);
7200                         Set_Is_Overloaded (N, False);
7201                         Generate_Reference (Entity (P), P);
7202                         exit;
7203                      end if;
7204
7205                      Get_Next_Interp (Index, It);
7206                   end loop;
7207
7208                --  If Prefix is a subprogram name, it is frozen by this
7209                --  reference:
7210
7211                --    If it is a type, there is nothing to resolve.
7212                --    If it is an object, complete its resolution.
7213
7214                elsif Is_Overloadable (Entity (P)) then
7215                   if not In_Default_Expression then
7216                      Insert_Actions (N, Freeze_Entity (Entity (P), Loc));
7217                   end if;
7218
7219                elsif Is_Type (Entity (P)) then
7220                   null;
7221                else
7222                   Resolve (P);
7223                end if;
7224
7225                Error_Msg_Name_1 := Aname;
7226
7227                if not Is_Entity_Name (P) then
7228                   null;
7229
7230                elsif Is_Overloadable (Entity (P))
7231                  and then Is_Abstract_Subprogram (Entity (P))
7232                then
7233                   Error_Msg_F ("prefix of % attribute cannot be abstract", P);
7234                   Set_Etype (N, Any_Type);
7235
7236                elsif Convention (Entity (P)) = Convention_Intrinsic then
7237                   if Ekind (Entity (P)) = E_Enumeration_Literal then
7238                      Error_Msg_F
7239                        ("prefix of % attribute cannot be enumeration literal",
7240                         P);
7241                   else
7242                      Error_Msg_F
7243                        ("prefix of % attribute cannot be intrinsic", P);
7244                   end if;
7245
7246                   Set_Etype (N, Any_Type);
7247                end if;
7248
7249                --  Assignments, return statements, components of aggregates,
7250                --  generic instantiations will require convention checks if
7251                --  the type is an access to subprogram. Given that there will
7252                --  also be accessibility checks on those, this is where the
7253                --  checks can eventually be centralized ???
7254
7255                if Ekind (Btyp) = E_Access_Subprogram_Type
7256                     or else
7257                   Ekind (Btyp) = E_Anonymous_Access_Subprogram_Type
7258                     or else
7259                   Ekind (Btyp) = E_Anonymous_Access_Protected_Subprogram_Type
7260                then
7261                   --  Deal with convention mismatch
7262
7263                   if Convention (Btyp) /= Convention (Entity (P)) then
7264                      Error_Msg_FE
7265                        ("subprogram & has wrong convention", P, Entity (P));
7266
7267                      Error_Msg_FE
7268                        ("\does not match convention of access type &",
7269                         P, Btyp);
7270
7271                      if not Has_Convention_Pragma (Btyp) then
7272                         Error_Msg_FE
7273                           ("\probable missing pragma Convention for &",
7274                            P, Btyp);
7275                      end if;
7276
7277                   else
7278                      Check_Subtype_Conformant
7279                        (New_Id  => Entity (P),
7280                         Old_Id  => Designated_Type (Btyp),
7281                         Err_Loc => P);
7282                   end if;
7283
7284                   if Attr_Id = Attribute_Unchecked_Access then
7285                      Error_Msg_Name_1 := Aname;
7286                      Error_Msg_F
7287                        ("attribute% cannot be applied to a subprogram", P);
7288
7289                   elsif Aname = Name_Unrestricted_Access then
7290                      null;  --  Nothing to check
7291
7292                   --  Check the static accessibility rule of 3.10.2(32).
7293                   --  This rule also applies within the private part of an
7294                   --  instantiation. This rule does not apply to anonymous
7295                   --  access-to-subprogram types (Ada 2005).
7296
7297                   elsif Attr_Id = Attribute_Access
7298                     and then not In_Instance_Body
7299                     and then Subprogram_Access_Level (Entity (P)) >
7300                                Type_Access_Level (Btyp)
7301                     and then Ekind (Btyp) /=
7302                                E_Anonymous_Access_Subprogram_Type
7303                     and then Ekind (Btyp) /=
7304                                E_Anonymous_Access_Protected_Subprogram_Type
7305                   then
7306                      Error_Msg_F
7307                        ("subprogram must not be deeper than access type", P);
7308
7309                   --  Check the restriction of 3.10.2(32) that disallows the
7310                   --  access attribute within a generic body when the ultimate
7311                   --  ancestor of the type of the attribute is declared outside
7312                   --  of the generic unit and the subprogram is declared within
7313                   --  that generic unit. This includes any such attribute that
7314                   --  occurs within the body of a generic unit that is a child
7315                   --  of the generic unit where the subprogram is declared.
7316                   --  The rule also prohibits applying the attibute when the
7317                   --  access type is a generic formal access type (since the
7318                   --  level of the actual type is not known). This restriction
7319                   --  does not apply when the attribute type is an anonymous
7320                   --  access-to-subprogram type. Note that this check was
7321                   --  revised by AI-229, because the originally Ada 95 rule
7322                   --  was too lax. The original rule only applied when the
7323                   --  subprogram was declared within the body of the generic,
7324                   --  which allowed the possibility of dangling references).
7325                   --  The rule was also too strict in some case, in that it
7326                   --  didn't permit the access to be declared in the generic
7327                   --  spec, whereas the revised rule does (as long as it's not
7328                   --  a formal type).
7329
7330                   --  There are a couple of subtleties of the test for applying
7331                   --  the check that are worth noting. First, we only apply it
7332                   --  when the levels of the subprogram and access type are the
7333                   --  same (the case where the subprogram is statically deeper
7334                   --  was applied above, and the case where the type is deeper
7335                   --  is always safe). Second, we want the check to apply
7336                   --  within nested generic bodies and generic child unit
7337                   --  bodies, but not to apply to an attribute that appears in
7338                   --  the generic unit's specification. This is done by testing
7339                   --  that the attribute's innermost enclosing generic body is
7340                   --  not the same as the innermost generic body enclosing the
7341                   --  generic unit where the subprogram is declared (we don't
7342                   --  want the check to apply when the access attribute is in
7343                   --  the spec and there's some other generic body enclosing
7344                   --  generic). Finally, there's no point applying the check
7345                   --  when within an instance, because any violations will have
7346                   --  been caught by the compilation of the generic unit.
7347
7348                   elsif Attr_Id = Attribute_Access
7349                     and then not In_Instance
7350                     and then Present (Enclosing_Generic_Unit (Entity (P)))
7351                     and then Present (Enclosing_Generic_Body (N))
7352                     and then Enclosing_Generic_Body (N) /=
7353                                Enclosing_Generic_Body
7354                                  (Enclosing_Generic_Unit (Entity (P)))
7355                     and then Subprogram_Access_Level (Entity (P)) =
7356                                Type_Access_Level (Btyp)
7357                     and then Ekind (Btyp) /=
7358                                E_Anonymous_Access_Subprogram_Type
7359                     and then Ekind (Btyp) /=
7360                                E_Anonymous_Access_Protected_Subprogram_Type
7361                   then
7362                      --  The attribute type's ultimate ancestor must be
7363                      --  declared within the same generic unit as the
7364                      --  subprogram is declared. The error message is
7365                      --  specialized to say "ancestor" for the case where
7366                      --  the access type is not its own ancestor, since
7367                      --  saying simply "access type" would be very confusing.
7368
7369                      if Enclosing_Generic_Unit (Entity (P)) /=
7370                           Enclosing_Generic_Unit (Root_Type (Btyp))
7371                      then
7372                         Error_Msg_N
7373                           ("''Access attribute not allowed in generic body",
7374                            N);
7375
7376                         if Root_Type (Btyp) = Btyp then
7377                            Error_Msg_NE
7378                              ("\because " &
7379                               "access type & is declared outside " &
7380                               "generic unit (RM 3.10.2(32))", N, Btyp);
7381                         else
7382                            Error_Msg_NE
7383                              ("\because ancestor of " &
7384                               "access type & is declared outside " &
7385                               "generic unit (RM 3.10.2(32))", N, Btyp);
7386                         end if;
7387
7388                         Error_Msg_NE
7389                           ("\move ''Access to private part, or " &
7390                            "(Ada 2005) use anonymous access type instead of &",
7391                            N, Btyp);
7392
7393                      --  If the ultimate ancestor of the attribute's type is
7394                      --  a formal type, then the attribute is illegal because
7395                      --  the actual type might be declared at a higher level.
7396                      --  The error message is specialized to say "ancestor"
7397                      --  for the case where the access type is not its own
7398                      --  ancestor, since saying simply "access type" would be
7399                      --  very confusing.
7400
7401                      elsif Is_Generic_Type (Root_Type (Btyp)) then
7402                         if Root_Type (Btyp) = Btyp then
7403                            Error_Msg_N
7404                              ("access type must not be a generic formal type",
7405                               N);
7406                         else
7407                            Error_Msg_N
7408                              ("ancestor access type must not be a generic " &
7409                               "formal type", N);
7410                         end if;
7411                      end if;
7412                   end if;
7413                end if;
7414
7415                --  If this is a renaming, an inherited operation, or a
7416                --  subprogram instance, use the original entity. This may make
7417                --  the node type-inconsistent, so this transformation can only
7418                --  be done if the node will not be reanalyzed. In particular,
7419                --  if it is within a default expression, the transformation
7420                --  must be delayed until the default subprogram is created for
7421                --  it, when the enclosing subprogram is frozen.
7422
7423                if Is_Entity_Name (P)
7424                  and then Is_Overloadable (Entity (P))
7425                  and then Present (Alias (Entity (P)))
7426                  and then Expander_Active
7427                then
7428                   Rewrite (P,
7429                     New_Occurrence_Of (Alias (Entity (P)), Sloc (P)));
7430                end if;
7431
7432             elsif Nkind (P) = N_Selected_Component
7433               and then Is_Overloadable (Entity (Selector_Name (P)))
7434             then
7435                --  Protected operation. If operation is overloaded, must
7436                --  disambiguate. Prefix that denotes protected object itself
7437                --  is resolved with its own type.
7438
7439                if Attr_Id = Attribute_Unchecked_Access then
7440                   Error_Msg_Name_1 := Aname;
7441                   Error_Msg_F
7442                     ("attribute% cannot be applied to protected operation", P);
7443                end if;
7444
7445                Resolve (Prefix (P));
7446                Generate_Reference (Entity (Selector_Name (P)), P);
7447
7448             elsif Is_Overloaded (P) then
7449
7450                --  Use the designated type of the context to disambiguate
7451                --  Note that this was not strictly conformant to Ada 95,
7452                --  but was the implementation adopted by most Ada 95 compilers.
7453                --  The use of the context type to resolve an Access attribute
7454                --  reference is now mandated in AI-235 for Ada 2005.
7455
7456                declare
7457                   Index : Interp_Index;
7458                   It    : Interp;
7459
7460                begin
7461                   Get_First_Interp (P, Index, It);
7462                   while Present (It.Typ) loop
7463                      if Covers (Designated_Type (Typ), It.Typ) then
7464                         Resolve (P, It.Typ);
7465                         exit;
7466                      end if;
7467
7468                      Get_Next_Interp (Index, It);
7469                   end loop;
7470                end;
7471             else
7472                Resolve (P);
7473             end if;
7474
7475             --  X'Access is illegal if X denotes a constant and the access type
7476             --  is access-to-variable. Same for 'Unchecked_Access. The rule
7477             --  does not apply to 'Unrestricted_Access. If the reference is a
7478             --  default-initialized aggregate component for a self-referential
7479             --  type the reference is legal.
7480
7481             if not (Ekind (Btyp) = E_Access_Subprogram_Type
7482                      or else Ekind (Btyp) = E_Anonymous_Access_Subprogram_Type
7483                      or else (Is_Record_Type (Btyp)
7484                                and then
7485                                  Present (Corresponding_Remote_Type (Btyp)))
7486                      or else Ekind (Btyp) = E_Access_Protected_Subprogram_Type
7487                      or else Ekind (Btyp)
7488                                = E_Anonymous_Access_Protected_Subprogram_Type
7489                      or else Is_Access_Constant (Btyp)
7490                      or else Is_Variable (P)
7491                      or else Attr_Id = Attribute_Unrestricted_Access)
7492             then
7493                if Is_Entity_Name (P)
7494                  and then Is_Type (Entity (P))
7495                then
7496                   --  Legality of a self-reference through an access
7497                   --  attribute has been verified in Analyze_Access_Attribute.
7498
7499                   null;
7500
7501                elsif Comes_From_Source (N) then
7502                   Error_Msg_F ("access-to-variable designates constant", P);
7503                end if;
7504             end if;
7505
7506             if (Attr_Id = Attribute_Access
7507                   or else
7508                 Attr_Id = Attribute_Unchecked_Access)
7509               and then (Ekind (Btyp) = E_General_Access_Type
7510                           or else Ekind (Btyp) = E_Anonymous_Access_Type)
7511             then
7512                --  Ada 2005 (AI-230): Check the accessibility of anonymous
7513                --  access types for stand-alone objects, record and array
7514                --  components, and return objects. For a component definition
7515                --  the level is the same of the enclosing composite type.
7516
7517                if Ada_Version >= Ada_05
7518                  and then Is_Local_Anonymous_Access (Btyp)
7519                  and then Object_Access_Level (P) > Type_Access_Level (Btyp)
7520                  and then Attr_Id = Attribute_Access
7521                then
7522                   --  In an instance, this is a runtime check, but one we
7523                   --  know will fail, so generate an appropriate warning.
7524
7525                   if In_Instance_Body then
7526                      Error_Msg_F
7527                        ("?non-local pointer cannot point to local object", P);
7528                      Error_Msg_F
7529                        ("\?Program_Error will be raised at run time", P);
7530                      Rewrite (N,
7531                        Make_Raise_Program_Error (Loc,
7532                          Reason => PE_Accessibility_Check_Failed));
7533                      Set_Etype (N, Typ);
7534
7535                   else
7536                      Error_Msg_F
7537                        ("non-local pointer cannot point to local object", P);
7538                   end if;
7539                end if;
7540
7541                if Is_Dependent_Component_Of_Mutable_Object (P) then
7542                   Error_Msg_F
7543                     ("illegal attribute for discriminant-dependent component",
7544                      P);
7545                end if;
7546
7547                --  Check static matching rule of 3.10.2(27). Nominal subtype
7548                --  of the prefix must statically match the designated type.
7549
7550                Nom_Subt := Etype (P);
7551
7552                if Is_Constr_Subt_For_U_Nominal (Nom_Subt) then
7553                   Nom_Subt := Base_Type (Nom_Subt);
7554                end if;
7555
7556                Des_Btyp := Designated_Type (Btyp);
7557
7558                if Ekind (Des_Btyp) = E_Incomplete_Subtype then
7559
7560                   --  Ada 2005 (AI-412): Subtypes of incomplete types visible
7561                   --  through a limited with clause or regular incomplete
7562                   --  subtypes.
7563
7564                   if From_With_Type (Des_Btyp)
7565                     and then Present (Non_Limited_View (Des_Btyp))
7566                   then
7567                      Des_Btyp := Non_Limited_View (Des_Btyp);
7568                   else
7569                      Des_Btyp := Etype (Des_Btyp);
7570                   end if;
7571                end if;
7572
7573                if Is_Tagged_Type (Designated_Type (Typ)) then
7574
7575                   --  If the attribute is in the context of an access
7576                   --  parameter, then the prefix is allowed to be of the
7577                   --  class-wide type (by AI-127).
7578
7579                   if Ekind (Typ) = E_Anonymous_Access_Type then
7580                      if not Covers (Designated_Type (Typ), Nom_Subt)
7581                        and then not Covers (Nom_Subt, Designated_Type (Typ))
7582                      then
7583                         declare
7584                            Desig : Entity_Id;
7585
7586                         begin
7587                            Desig := Designated_Type (Typ);
7588
7589                            if Is_Class_Wide_Type (Desig) then
7590                               Desig := Etype (Desig);
7591                            end if;
7592
7593                            if Is_Anonymous_Tagged_Base (Nom_Subt, Desig) then
7594                               null;
7595
7596                            else
7597                               Error_Msg_FE
7598                                 ("type of prefix: & not compatible",
7599                                   P, Nom_Subt);
7600                               Error_Msg_FE
7601                                 ("\with &, the expected designated type",
7602                                   P, Designated_Type (Typ));
7603                            end if;
7604                         end;
7605                      end if;
7606
7607                   elsif not Covers (Designated_Type (Typ), Nom_Subt)
7608                     or else
7609                       (not Is_Class_Wide_Type (Designated_Type (Typ))
7610                         and then Is_Class_Wide_Type (Nom_Subt))
7611                   then
7612                      Error_Msg_FE
7613                        ("type of prefix: & is not covered", P, Nom_Subt);
7614                      Error_Msg_FE
7615                        ("\by &, the expected designated type" &
7616                            " (RM 3.10.2 (27))", P, Designated_Type (Typ));
7617                   end if;
7618
7619                   if Is_Class_Wide_Type (Designated_Type (Typ))
7620                     and then Has_Discriminants (Etype (Designated_Type (Typ)))
7621                     and then Is_Constrained (Etype (Designated_Type (Typ)))
7622                     and then Designated_Type (Typ) /= Nom_Subt
7623                   then
7624                      Apply_Discriminant_Check
7625                        (N, Etype (Designated_Type (Typ)));
7626                   end if;
7627
7628                --  Ada 2005 (AI-363): Require static matching when designated
7629                --  type has discriminants and a constrained partial view, since
7630                --  in general objects of such types are mutable, so we can't
7631                --  allow the access value to designate a constrained object
7632                --  (because access values must be assumed to designate mutable
7633                --  objects when designated type does not impose a constraint).
7634
7635                elsif not Subtypes_Statically_Match (Des_Btyp, Nom_Subt)
7636                  and then
7637                    not (Has_Discriminants (Designated_Type (Typ))
7638                           and then not Is_Constrained (Des_Btyp)
7639                           and then
7640                             (Ada_Version < Ada_05
7641                               or else
7642                                 not Has_Constrained_Partial_View
7643                                       (Designated_Type (Base_Type (Typ)))))
7644                then
7645                   Error_Msg_F
7646                     ("object subtype must statically match "
7647                      & "designated subtype", P);
7648
7649                   if Is_Entity_Name (P)
7650                     and then Is_Array_Type (Designated_Type (Typ))
7651                   then
7652                      declare
7653                         D : constant Node_Id := Declaration_Node (Entity (P));
7654
7655                      begin
7656                         Error_Msg_N ("aliased object has explicit bounds?",
7657                           D);
7658                         Error_Msg_N ("\declare without bounds"
7659                           & " (and with explicit initialization)?", D);
7660                         Error_Msg_N ("\for use with unconstrained access?", D);
7661                      end;
7662                   end if;
7663                end if;
7664
7665                --  Check the static accessibility rule of 3.10.2(28).
7666                --  Note that this check is not performed for the
7667                --  case of an anonymous access type, since the access
7668                --  attribute is always legal in such a context.
7669
7670                if Attr_Id /= Attribute_Unchecked_Access
7671                  and then Object_Access_Level (P) > Type_Access_Level (Btyp)
7672                  and then Ekind (Btyp) = E_General_Access_Type
7673                then
7674                   Accessibility_Message;
7675                   return;
7676                end if;
7677             end if;
7678
7679             if Ekind (Btyp) = E_Access_Protected_Subprogram_Type
7680                  or else
7681                Ekind (Btyp) = E_Anonymous_Access_Protected_Subprogram_Type
7682             then
7683                if Is_Entity_Name (P)
7684                  and then not Is_Protected_Type (Scope (Entity (P)))
7685                then
7686                   Error_Msg_F ("context requires a protected subprogram", P);
7687
7688                --  Check accessibility of protected object against that of the
7689                --  access type, but only on user code, because the expander
7690                --  creates access references for handlers. If the context is an
7691                --  anonymous_access_to_protected, there are no accessibility
7692                --  checks either. Omit check entirely for Unrestricted_Access.
7693
7694                elsif Object_Access_Level (P) > Type_Access_Level (Btyp)
7695                  and then Comes_From_Source (N)
7696                  and then Ekind (Btyp) = E_Access_Protected_Subprogram_Type
7697                  and then Attr_Id /= Attribute_Unrestricted_Access
7698                then
7699                   Accessibility_Message;
7700                   return;
7701                end if;
7702
7703             elsif (Ekind (Btyp) = E_Access_Subprogram_Type
7704                      or else
7705                    Ekind (Btyp) = E_Anonymous_Access_Subprogram_Type)
7706               and then Ekind (Etype (N)) = E_Access_Protected_Subprogram_Type
7707             then
7708                Error_Msg_F ("context requires a non-protected subprogram", P);
7709             end if;
7710
7711             --  The context cannot be a pool-specific type, but this is a
7712             --  legality rule, not a resolution rule, so it must be checked
7713             --  separately, after possibly disambiguation (see AI-245).
7714
7715             if Ekind (Btyp) = E_Access_Type
7716               and then Attr_Id /= Attribute_Unrestricted_Access
7717             then
7718                Wrong_Type (N, Typ);
7719             end if;
7720
7721             --  The context may be a constrained access type (however ill-
7722             --  advised such subtypes might be) so in order to generate a
7723             --  constraint check when needed set the type of the attribute
7724             --  reference to the base type of the context.
7725
7726             Set_Etype (N, Btyp);
7727
7728             --  Check for incorrect atomic/volatile reference (RM C.6(12))
7729
7730             if Attr_Id /= Attribute_Unrestricted_Access then
7731                if Is_Atomic_Object (P)
7732                  and then not Is_Atomic (Designated_Type (Typ))
7733                then
7734                   Error_Msg_F
7735                     ("access to atomic object cannot yield access-to-" &
7736                      "non-atomic type", P);
7737
7738                elsif Is_Volatile_Object (P)
7739                  and then not Is_Volatile (Designated_Type (Typ))
7740                then
7741                   Error_Msg_F
7742                     ("access to volatile object cannot yield access-to-" &
7743                      "non-volatile type", P);
7744                end if;
7745             end if;
7746
7747             if Is_Entity_Name (P) then
7748                Set_Address_Taken (Entity (P));
7749             end if;
7750          end Access_Attribute;
7751
7752          -------------
7753          -- Address --
7754          -------------
7755
7756          --  Deal with resolving the type for Address attribute, overloading
7757          --  is not permitted here, since there is no context to resolve it.
7758
7759          when Attribute_Address | Attribute_Code_Address =>
7760          Address_Attribute : begin
7761
7762             --  To be safe, assume that if the address of a variable is taken,
7763             --  it may be modified via this address, so note modification.
7764
7765             if Is_Variable (P) then
7766                Note_Possible_Modification (P);
7767             end if;
7768
7769             if Nkind (P) in N_Subexpr
7770               and then Is_Overloaded (P)
7771             then
7772                Get_First_Interp (P, Index, It);
7773                Get_Next_Interp (Index, It);
7774
7775                if Present (It.Nam) then
7776                   Error_Msg_Name_1 := Aname;
7777                   Error_Msg_F
7778                     ("prefix of % attribute cannot be overloaded", P);
7779                end if;
7780             end if;
7781
7782             if not Is_Entity_Name (P)
7783               or else not Is_Overloadable (Entity (P))
7784             then
7785                if not Is_Task_Type (Etype (P))
7786                  or else Nkind (P) = N_Explicit_Dereference
7787                then
7788                   Resolve (P);
7789                end if;
7790             end if;
7791
7792             --  If this is the name of a derived subprogram, or that of a
7793             --  generic actual, the address is that of the original entity.
7794
7795             if Is_Entity_Name (P)
7796               and then Is_Overloadable (Entity (P))
7797               and then Present (Alias (Entity (P)))
7798             then
7799                Rewrite (P,
7800                  New_Occurrence_Of (Alias (Entity (P)), Sloc (P)));
7801             end if;
7802
7803             if Is_Entity_Name (P) then
7804                Set_Address_Taken (Entity (P));
7805             end if;
7806          end Address_Attribute;
7807
7808          ---------------
7809          -- AST_Entry --
7810          ---------------
7811
7812          --  Prefix of the AST_Entry attribute is an entry name which must
7813          --  not be resolved, since this is definitely not an entry call.
7814
7815          when Attribute_AST_Entry =>
7816             null;
7817
7818          ------------------
7819          -- Body_Version --
7820          ------------------
7821
7822          --  Prefix of Body_Version attribute can be a subprogram name which
7823          --  must not be resolved, since this is not a call.
7824
7825          when Attribute_Body_Version =>
7826             null;
7827
7828          ------------
7829          -- Caller --
7830          ------------
7831
7832          --  Prefix of Caller attribute is an entry name which must not
7833          --  be resolved, since this is definitely not an entry call.
7834
7835          when Attribute_Caller =>
7836             null;
7837
7838          ------------------
7839          -- Code_Address --
7840          ------------------
7841
7842          --  Shares processing with Address attribute
7843
7844          -----------
7845          -- Count --
7846          -----------
7847
7848          --  If the prefix of the Count attribute is an entry name it must not
7849          --  be resolved, since this is definitely not an entry call. However,
7850          --  if it is an element of an entry family, the index itself may
7851          --  have to be resolved because it can be a general expression.
7852
7853          when Attribute_Count =>
7854             if Nkind (P) = N_Indexed_Component
7855               and then Is_Entity_Name (Prefix (P))
7856             then
7857                declare
7858                   Indx : constant Node_Id   := First (Expressions (P));
7859                   Fam  : constant Entity_Id := Entity (Prefix (P));
7860                begin
7861                   Resolve (Indx, Entry_Index_Type (Fam));
7862                   Apply_Range_Check (Indx, Entry_Index_Type (Fam));
7863                end;
7864             end if;
7865
7866          ----------------
7867          -- Elaborated --
7868          ----------------
7869
7870          --  Prefix of the Elaborated attribute is a subprogram name which
7871          --  must not be resolved, since this is definitely not a call. Note
7872          --  that it is a library unit, so it cannot be overloaded here.
7873
7874          when Attribute_Elaborated =>
7875             null;
7876
7877          -------------
7878          -- Enabled --
7879          -------------
7880
7881          --  Prefix of Enabled attribute is a check name, which must be treated
7882          --  specially and not touched by Resolve.
7883
7884          when Attribute_Enabled =>
7885             null;
7886
7887          --------------------
7888          -- Mechanism_Code --
7889          --------------------
7890
7891          --  Prefix of the Mechanism_Code attribute is a function name
7892          --  which must not be resolved. Should we check for overloaded ???
7893
7894          when Attribute_Mechanism_Code =>
7895             null;
7896
7897          ------------------
7898          -- Partition_ID --
7899          ------------------
7900
7901          --  Most processing is done in sem_dist, after determining the
7902          --  context type. Node is rewritten as a conversion to a runtime call.
7903
7904          when Attribute_Partition_ID =>
7905             Process_Partition_Id (N);
7906             return;
7907
7908          when Attribute_Pool_Address =>
7909             Resolve (P);
7910
7911          -----------
7912          -- Range --
7913          -----------
7914
7915          --  We replace the Range attribute node with a range expression
7916          --  whose bounds are the 'First and 'Last attributes applied to the
7917          --  same prefix. The reason that we do this transformation here
7918          --  instead of in the expander is that it simplifies other parts of
7919          --  the semantic analysis which assume that the Range has been
7920          --  replaced; thus it must be done even when in semantic-only mode
7921          --  (note that the RM specifically mentions this equivalence, we
7922          --  take care that the prefix is only evaluated once).
7923
7924          when Attribute_Range => Range_Attribute :
7925             declare
7926                LB   : Node_Id;
7927                HB   : Node_Id;
7928
7929                function Check_Discriminated_Prival
7930                  (N    : Node_Id)
7931                   return Node_Id;
7932                --  The range of a private component constrained by a
7933                --  discriminant is rewritten to make the discriminant
7934                --  explicit. This solves some complex visibility problems
7935                --  related to the use of privals.
7936
7937                --------------------------------
7938                -- Check_Discriminated_Prival --
7939                --------------------------------
7940
7941                function Check_Discriminated_Prival
7942                  (N    : Node_Id)
7943                   return Node_Id
7944                is
7945                begin
7946                   if Is_Entity_Name (N)
7947                     and then Ekind (Entity (N)) = E_In_Parameter
7948                     and then not Within_Init_Proc
7949                   then
7950                      return Make_Identifier (Sloc (N), Chars (Entity (N)));
7951                   else
7952                      return Duplicate_Subexpr (N);
7953                   end if;
7954                end Check_Discriminated_Prival;
7955
7956             --  Start of processing for Range_Attribute
7957
7958             begin
7959                if not Is_Entity_Name (P)
7960                  or else not Is_Type (Entity (P))
7961                then
7962                   Resolve (P);
7963                end if;
7964
7965                --  Check whether prefix is (renaming of) private component
7966                --  of protected type.
7967
7968                if Is_Entity_Name (P)
7969                  and then Comes_From_Source (N)
7970                  and then Is_Array_Type (Etype (P))
7971                  and then Number_Dimensions (Etype (P)) = 1
7972                  and then (Ekind (Scope (Entity (P))) = E_Protected_Type
7973                             or else
7974                            Ekind (Scope (Scope (Entity (P)))) =
7975                                                         E_Protected_Type)
7976                then
7977                   LB :=
7978                     Check_Discriminated_Prival
7979                       (Type_Low_Bound (Etype (First_Index (Etype (P)))));
7980
7981                   HB :=
7982                     Check_Discriminated_Prival
7983                       (Type_High_Bound (Etype (First_Index (Etype (P)))));
7984
7985                else
7986                   HB :=
7987                     Make_Attribute_Reference (Loc,
7988                       Prefix         => Duplicate_Subexpr (P),
7989                       Attribute_Name => Name_Last,
7990                       Expressions    => Expressions (N));
7991
7992                   LB :=
7993                     Make_Attribute_Reference (Loc,
7994                       Prefix         => P,
7995                       Attribute_Name => Name_First,
7996                       Expressions    => Expressions (N));
7997                end if;
7998
7999                --  If the original was marked as Must_Not_Freeze (see code
8000                --  in Sem_Ch3.Make_Index), then make sure the rewriting
8001                --  does not freeze either.
8002
8003                if Must_Not_Freeze (N) then
8004                   Set_Must_Not_Freeze (HB);
8005                   Set_Must_Not_Freeze (LB);
8006                   Set_Must_Not_Freeze (Prefix (HB));
8007                   Set_Must_Not_Freeze (Prefix (LB));
8008                end if;
8009
8010                if Raises_Constraint_Error (Prefix (N)) then
8011
8012                   --  Preserve Sloc of prefix in the new bounds, so that
8013                   --  the posted warning can be removed if we are within
8014                   --  unreachable code.
8015
8016                   Set_Sloc (LB, Sloc (Prefix (N)));
8017                   Set_Sloc (HB, Sloc (Prefix (N)));
8018                end if;
8019
8020                Rewrite (N, Make_Range (Loc, LB, HB));
8021                Analyze_And_Resolve (N, Typ);
8022
8023                --  Normally after resolving attribute nodes, Eval_Attribute
8024                --  is called to do any possible static evaluation of the node.
8025                --  However, here since the Range attribute has just been
8026                --  transformed into a range expression it is no longer an
8027                --  attribute node and therefore the call needs to be avoided
8028                --  and is accomplished by simply returning from the procedure.
8029
8030                return;
8031             end Range_Attribute;
8032
8033          -----------------
8034          -- UET_Address --
8035          -----------------
8036
8037          --  Prefix must not be resolved in this case, since it is not a
8038          --  real entity reference. No action of any kind is require!
8039
8040          when Attribute_UET_Address =>
8041             return;
8042
8043          ----------------------
8044          -- Unchecked_Access --
8045          ----------------------
8046
8047          --  Processing is shared with Access
8048
8049          -------------------------
8050          -- Unrestricted_Access --
8051          -------------------------
8052
8053          --  Processing is shared with Access
8054
8055          ---------
8056          -- Val --
8057          ---------
8058
8059          --  Apply range check. Note that we did not do this during the
8060          --  analysis phase, since we wanted Eval_Attribute to have a
8061          --  chance at finding an illegal out of range value.
8062
8063          when Attribute_Val =>
8064
8065             --  Note that we do our own Eval_Attribute call here rather than
8066             --  use the common one, because we need to do processing after
8067             --  the call, as per above comment.
8068
8069             Eval_Attribute (N);
8070
8071             --  Eval_Attribute may replace the node with a raise CE, or
8072             --  fold it to a constant. Obviously we only apply a scalar
8073             --  range check if this did not happen!
8074
8075             if Nkind (N) = N_Attribute_Reference
8076               and then Attribute_Name (N) = Name_Val
8077             then
8078                Apply_Scalar_Range_Check (First (Expressions (N)), Btyp);
8079             end if;
8080
8081             return;
8082
8083          -------------
8084          -- Version --
8085          -------------
8086
8087          --  Prefix of Version attribute can be a subprogram name which
8088          --  must not be resolved, since this is not a call.
8089
8090          when Attribute_Version =>
8091             null;
8092
8093          ----------------------
8094          -- Other Attributes --
8095          ----------------------
8096
8097          --  For other attributes, resolve prefix unless it is a type. If
8098          --  the attribute reference itself is a type name ('Base and 'Class)
8099          --  then this is only legal within a task or protected record.
8100
8101          when others =>
8102             if not Is_Entity_Name (P)
8103               or else not Is_Type (Entity (P))
8104             then
8105                Resolve (P);
8106             end if;
8107
8108             --  If the attribute reference itself is a type name ('Base,
8109             --  'Class) then this is only legal within a task or protected
8110             --  record. What is this all about ???
8111
8112             if Is_Entity_Name (N)
8113               and then Is_Type (Entity (N))
8114             then
8115                if Is_Concurrent_Type (Entity (N))
8116                  and then In_Open_Scopes (Entity (P))
8117                then
8118                   null;
8119                else
8120                   Error_Msg_N
8121                     ("invalid use of subtype name in expression or call", N);
8122                end if;
8123             end if;
8124
8125             --  For attributes whose argument may be a string, complete
8126             --  resolution of argument now. This avoids premature expansion
8127             --  (and the creation of transient scopes) before the attribute
8128             --  reference is resolved.
8129
8130             case Attr_Id is
8131                when Attribute_Value =>
8132                   Resolve (First (Expressions (N)), Standard_String);
8133
8134                when Attribute_Wide_Value =>
8135                   Resolve (First (Expressions (N)), Standard_Wide_String);
8136
8137                when Attribute_Wide_Wide_Value =>
8138                   Resolve (First (Expressions (N)), Standard_Wide_Wide_String);
8139
8140                when others => null;
8141             end case;
8142
8143             --  If the prefix of the attribute is a class-wide type then it
8144             --  will be expanded into a dispatching call to a predefined
8145             --  primitive. Therefore we must check for potential violation
8146             --  of such restriction.
8147
8148             if Is_Class_Wide_Type (Etype (P)) then
8149                Check_Restriction (No_Dispatching_Calls, N);
8150             end if;
8151       end case;
8152
8153       --  Normally the Freezing is done by Resolve but sometimes the Prefix
8154       --  is not resolved, in which case the freezing must be done now.
8155
8156       Freeze_Expression (P);
8157
8158       --  Finally perform static evaluation on the attribute reference
8159
8160       Eval_Attribute (N);
8161    end Resolve_Attribute;
8162
8163    --------------------------------
8164    -- Stream_Attribute_Available --
8165    --------------------------------
8166
8167    function Stream_Attribute_Available
8168      (Typ          : Entity_Id;
8169       Nam          : TSS_Name_Type;
8170       Partial_View : Node_Id := Empty) return Boolean
8171    is
8172       Etyp : Entity_Id := Typ;
8173
8174    --  Start of processing for Stream_Attribute_Available
8175
8176    begin
8177       --  We need some comments in this body ???
8178
8179       if Has_Stream_Attribute_Definition (Typ, Nam) then
8180          return True;
8181       end if;
8182
8183       if Is_Class_Wide_Type (Typ) then
8184          return not Is_Limited_Type (Typ)
8185            or else Stream_Attribute_Available (Etype (Typ), Nam);
8186       end if;
8187
8188       if Nam = TSS_Stream_Input
8189         and then Is_Abstract_Type (Typ)
8190         and then not Is_Class_Wide_Type (Typ)
8191       then
8192          return False;
8193       end if;
8194
8195       if not (Is_Limited_Type (Typ)
8196         or else (Present (Partial_View)
8197                    and then Is_Limited_Type (Partial_View)))
8198       then
8199          return True;
8200       end if;
8201
8202       --  In Ada 2005, Input can invoke Read, and Output can invoke Write
8203
8204       if Nam = TSS_Stream_Input
8205         and then Ada_Version >= Ada_05
8206         and then Stream_Attribute_Available (Etyp, TSS_Stream_Read)
8207       then
8208          return True;
8209
8210       elsif Nam = TSS_Stream_Output
8211         and then Ada_Version >= Ada_05
8212         and then Stream_Attribute_Available (Etyp, TSS_Stream_Write)
8213       then
8214          return True;
8215       end if;
8216
8217       --  Case of Read and Write: check for attribute definition clause that
8218       --  applies to an ancestor type.
8219
8220       while Etype (Etyp) /= Etyp loop
8221          Etyp := Etype (Etyp);
8222
8223          if Has_Stream_Attribute_Definition (Etyp, Nam) then
8224             return True;
8225          end if;
8226       end loop;
8227
8228       if Ada_Version < Ada_05 then
8229
8230          --  In Ada 95 mode, also consider a non-visible definition
8231
8232          declare
8233             Btyp : constant Entity_Id := Implementation_Base_Type (Typ);
8234          begin
8235             return Btyp /= Typ
8236               and then Stream_Attribute_Available
8237                          (Btyp, Nam, Partial_View => Typ);
8238          end;
8239       end if;
8240
8241       return False;
8242    end Stream_Attribute_Available;
8243
8244 end Sem_Attr;