OSDN Git Service

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