OSDN Git Service

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