OSDN Git Service

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