OSDN Git Service

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