OSDN Git Service

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