OSDN Git Service

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