OSDN Git Service

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