OSDN Git Service

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