OSDN Git Service

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