OSDN Git Service

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