OSDN Git Service

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