OSDN Git Service

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