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