OSDN Git Service

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