OSDN Git Service

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