OSDN Git Service

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