OSDN Git Service

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