OSDN Git Service

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