OSDN Git Service

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