OSDN Git Service

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