OSDN Git Service

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