OSDN Git Service

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