OSDN Git Service

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