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