OSDN Git Service

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