OSDN Git Service

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