OSDN Git Service

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