OSDN Git Service

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