OSDN Git Service

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