OSDN Git Service

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