OSDN Git Service

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