OSDN Git Service

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