OSDN Git Service

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