2014-08-04 Robert Dewar <dewar@adacore.com>
[official-gcc.git] / gcc / ada / sem_attr.adb
blobcdb3cfe33c2b34308f507817d678a236b3093f86
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-2014, 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 Debug; use Debug;
32 with Einfo; use Einfo;
33 with Elists; use Elists;
34 with Errout; use Errout;
35 with Eval_Fat;
36 with Exp_Dist; use Exp_Dist;
37 with Exp_Util; use Exp_Util;
38 with Expander; use Expander;
39 with Freeze; use Freeze;
40 with Gnatvsn; use Gnatvsn;
41 with Itypes; use Itypes;
42 with Lib; use Lib;
43 with Lib.Xref; use Lib.Xref;
44 with Nlists; use Nlists;
45 with Nmake; use Nmake;
46 with Opt; use Opt;
47 with Restrict; use Restrict;
48 with Rident; use Rident;
49 with Rtsfind; use Rtsfind;
50 with Sdefault; use Sdefault;
51 with Sem; use Sem;
52 with Sem_Aux; use Sem_Aux;
53 with Sem_Cat; use Sem_Cat;
54 with Sem_Ch6; use Sem_Ch6;
55 with Sem_Ch8; use Sem_Ch8;
56 with Sem_Ch10; use Sem_Ch10;
57 with Sem_Dim; use Sem_Dim;
58 with Sem_Dist; use Sem_Dist;
59 with Sem_Elab; use Sem_Elab;
60 with Sem_Elim; use Sem_Elim;
61 with Sem_Eval; use Sem_Eval;
62 with Sem_Res; use Sem_Res;
63 with Sem_Type; use Sem_Type;
64 with Sem_Util; use Sem_Util;
65 with Stand; use Stand;
66 with Sinfo; use Sinfo;
67 with Sinput; use Sinput;
68 with System;
69 with Stringt; use Stringt;
70 with Style;
71 with Stylesw; use Stylesw;
72 with Targparm; use Targparm;
73 with Ttypes; use Ttypes;
74 with Tbuild; use Tbuild;
75 with Uintp; use Uintp;
76 with Uname; use Uname;
77 with Urealp; use Urealp;
79 package body Sem_Attr is
81 True_Value : constant Uint := Uint_1;
82 False_Value : constant Uint := Uint_0;
83 -- Synonyms to be used when these constants are used as Boolean values
85 Bad_Attribute : exception;
86 -- Exception raised if an error is detected during attribute processing,
87 -- used so that we can abandon the processing so we don't run into
88 -- trouble with cascaded errors.
90 -- The following array is the list of attributes defined in the Ada 83 RM.
91 -- In Ada 83 mode, these are the only recognized attributes. In other Ada
92 -- modes all these attributes are recognized, even if removed in Ada 95.
94 Attribute_83 : constant Attribute_Class_Array := Attribute_Class_Array'(
95 Attribute_Address |
96 Attribute_Aft |
97 Attribute_Alignment |
98 Attribute_Base |
99 Attribute_Callable |
100 Attribute_Constrained |
101 Attribute_Count |
102 Attribute_Delta |
103 Attribute_Digits |
104 Attribute_Emax |
105 Attribute_Epsilon |
106 Attribute_First |
107 Attribute_First_Bit |
108 Attribute_Fore |
109 Attribute_Image |
110 Attribute_Large |
111 Attribute_Last |
112 Attribute_Last_Bit |
113 Attribute_Leading_Part |
114 Attribute_Length |
115 Attribute_Machine_Emax |
116 Attribute_Machine_Emin |
117 Attribute_Machine_Mantissa |
118 Attribute_Machine_Overflows |
119 Attribute_Machine_Radix |
120 Attribute_Machine_Rounds |
121 Attribute_Mantissa |
122 Attribute_Pos |
123 Attribute_Position |
124 Attribute_Pred |
125 Attribute_Range |
126 Attribute_Safe_Emax |
127 Attribute_Safe_Large |
128 Attribute_Safe_Small |
129 Attribute_Size |
130 Attribute_Small |
131 Attribute_Storage_Size |
132 Attribute_Succ |
133 Attribute_Terminated |
134 Attribute_Val |
135 Attribute_Value |
136 Attribute_Width => True,
137 others => False);
139 -- The following array is the list of attributes defined in the Ada 2005
140 -- RM which are not defined in Ada 95. These are recognized in Ada 95 mode,
141 -- but in Ada 95 they are considered to be implementation defined.
143 Attribute_05 : constant Attribute_Class_Array := Attribute_Class_Array'(
144 Attribute_Machine_Rounding |
145 Attribute_Mod |
146 Attribute_Priority |
147 Attribute_Stream_Size |
148 Attribute_Wide_Wide_Width => True,
149 others => False);
151 -- The following array is the list of attributes defined in the Ada 2012
152 -- RM which are not defined in Ada 2005. These are recognized in Ada 95
153 -- and Ada 2005 modes, but are considered to be implementation defined.
155 Attribute_12 : constant Attribute_Class_Array := Attribute_Class_Array'(
156 Attribute_First_Valid |
157 Attribute_Has_Same_Storage |
158 Attribute_Last_Valid |
159 Attribute_Max_Alignment_For_Allocation => True,
160 others => False);
162 -- The following array contains all attributes that imply a modification
163 -- of their prefixes or result in an access value. Such prefixes can be
164 -- considered as lvalues.
166 Attribute_Name_Implies_Lvalue_Prefix : constant Attribute_Class_Array :=
167 Attribute_Class_Array'(
168 Attribute_Access |
169 Attribute_Address |
170 Attribute_Input |
171 Attribute_Read |
172 Attribute_Unchecked_Access |
173 Attribute_Unrestricted_Access => True,
174 others => False);
176 -----------------------
177 -- Local_Subprograms --
178 -----------------------
180 procedure Eval_Attribute (N : Node_Id);
181 -- Performs compile time evaluation of attributes where possible, leaving
182 -- the Is_Static_Expression/Raises_Constraint_Error flags appropriately
183 -- set, and replacing the node with a literal node if the value can be
184 -- computed at compile time. All static attribute references are folded,
185 -- as well as a number of cases of non-static attributes that can always
186 -- be computed at compile time (e.g. floating-point model attributes that
187 -- are applied to non-static subtypes). Of course in such cases, the
188 -- Is_Static_Expression flag will not be set on the resulting literal.
189 -- Note that the only required action of this procedure is to catch the
190 -- static expression cases as described in the RM. Folding of other cases
191 -- is done where convenient, but some additional non-static folding is in
192 -- Expand_N_Attribute_Reference in cases where this is more convenient.
194 function Is_Anonymous_Tagged_Base
195 (Anon : Entity_Id;
196 Typ : Entity_Id) return Boolean;
197 -- For derived tagged types that constrain parent discriminants we build
198 -- an anonymous unconstrained base type. We need to recognize the relation
199 -- between the two when analyzing an access attribute for a constrained
200 -- component, before the full declaration for Typ has been analyzed, and
201 -- where therefore the prefix of the attribute does not match the enclosing
202 -- scope.
204 procedure Set_Boolean_Result (N : Node_Id; B : Boolean);
205 -- Rewrites node N with an occurrence of either Standard_False or
206 -- Standard_True, depending on the value of the parameter B. The
207 -- result is marked as a static expression.
209 -----------------------
210 -- Analyze_Attribute --
211 -----------------------
213 procedure Analyze_Attribute (N : Node_Id) is
214 Loc : constant Source_Ptr := Sloc (N);
215 Aname : constant Name_Id := Attribute_Name (N);
216 P : constant Node_Id := Prefix (N);
217 Exprs : constant List_Id := Expressions (N);
218 Attr_Id : constant Attribute_Id := Get_Attribute_Id (Aname);
219 E1 : Node_Id;
220 E2 : Node_Id;
222 P_Type : Entity_Id;
223 -- Type of prefix after analysis
225 P_Base_Type : Entity_Id;
226 -- Base type of prefix after analysis
228 -----------------------
229 -- Local Subprograms --
230 -----------------------
232 procedure Address_Checks;
233 -- Semantic checks for valid use of Address attribute. This was made
234 -- a separate routine with the idea of using it for unrestricted access
235 -- which seems like it should follow the same rules, but that turned
236 -- out to be impractical. So now this is only used for Address.
238 procedure Analyze_Access_Attribute;
239 -- Used for Access, Unchecked_Access, Unrestricted_Access attributes.
240 -- Internally, Id distinguishes which of the three cases is involved.
242 procedure Bad_Attribute_For_Predicate;
243 -- Output error message for use of a predicate (First, Last, Range) not
244 -- allowed with a type that has predicates. If the type is a generic
245 -- actual, then the message is a warning, and we generate code to raise
246 -- program error with an appropriate reason. No error message is given
247 -- for internally generated uses of the attributes. This legality rule
248 -- only applies to scalar types.
250 procedure Check_Array_Or_Scalar_Type;
251 -- Common procedure used by First, Last, Range attribute to check
252 -- that the prefix is a constrained array or scalar type, or a name
253 -- of an array object, and that an argument appears only if appropriate
254 -- (i.e. only in the array case).
256 procedure Check_Array_Type;
257 -- Common semantic checks for all array attributes. Checks that the
258 -- prefix is a constrained array type or the name of an array object.
259 -- The error message for non-arrays is specialized appropriately.
261 procedure Check_Asm_Attribute;
262 -- Common semantic checks for Asm_Input and Asm_Output attributes
264 procedure Check_Component;
265 -- Common processing for Bit_Position, First_Bit, Last_Bit, and
266 -- Position. Checks prefix is an appropriate selected component.
268 procedure Check_Decimal_Fixed_Point_Type;
269 -- Check that prefix of attribute N is a decimal fixed-point type
271 procedure Check_Dereference;
272 -- If the prefix of attribute is an object of an access type, then
273 -- introduce an explicit dereference, and adjust P_Type accordingly.
275 procedure Check_Discrete_Type;
276 -- Verify that prefix of attribute N is a discrete type
278 procedure Check_E0;
279 -- Check that no attribute arguments are present
281 procedure Check_Either_E0_Or_E1;
282 -- Check that there are zero or one attribute arguments present
284 procedure Check_E1;
285 -- Check that exactly one attribute argument is present
287 procedure Check_E2;
288 -- Check that two attribute arguments are present
290 procedure Check_Enum_Image;
291 -- If the prefix type is an enumeration type, set all its literals
292 -- as referenced, since the image function could possibly end up
293 -- referencing any of the literals indirectly. Same for Enum_Val.
294 -- Set the flag only if the reference is in the main code unit. Same
295 -- restriction when resolving 'Value; otherwise an improperly set
296 -- reference when analyzing an inlined body will lose a proper warning
297 -- on a useless with_clause.
299 procedure Check_First_Last_Valid;
300 -- Perform all checks for First_Valid and Last_Valid attributes
302 procedure Check_Fixed_Point_Type;
303 -- Verify that prefix of attribute N is a fixed type
305 procedure Check_Fixed_Point_Type_0;
306 -- Verify that prefix of attribute N is a fixed type and that
307 -- no attribute expressions are present
309 procedure Check_Floating_Point_Type;
310 -- Verify that prefix of attribute N is a float type
312 procedure Check_Floating_Point_Type_0;
313 -- Verify that prefix of attribute N is a float type and that
314 -- no attribute expressions are present
316 procedure Check_Floating_Point_Type_1;
317 -- Verify that prefix of attribute N is a float type and that
318 -- exactly one attribute expression is present
320 procedure Check_Floating_Point_Type_2;
321 -- Verify that prefix of attribute N is a float type and that
322 -- two attribute expressions are present
324 procedure Check_SPARK_05_Restriction_On_Attribute;
325 -- Issue an error in formal mode because attribute N is allowed
327 procedure Check_Integer_Type;
328 -- Verify that prefix of attribute N is an integer type
330 procedure Check_Modular_Integer_Type;
331 -- Verify that prefix of attribute N is a modular integer type
333 procedure Check_Not_CPP_Type;
334 -- Check that P (the prefix of the attribute) is not an CPP type
335 -- for which no Ada predefined primitive is available.
337 procedure Check_Not_Incomplete_Type;
338 -- Check that P (the prefix of the attribute) is not an incomplete
339 -- type or a private type for which no full view has been given.
341 procedure Check_Object_Reference (P : Node_Id);
342 -- Check that P is an object reference
344 procedure Check_Program_Unit;
345 -- Verify that prefix of attribute N is a program unit
347 procedure Check_Real_Type;
348 -- Verify that prefix of attribute N is fixed or float type
350 procedure Check_Scalar_Type;
351 -- Verify that prefix of attribute N is a scalar type
353 procedure Check_Standard_Prefix;
354 -- Verify that prefix of attribute N is package Standard. Also checks
355 -- that there are no arguments.
357 procedure Check_Stream_Attribute (Nam : TSS_Name_Type);
358 -- Validity checking for stream attribute. Nam is the TSS name of the
359 -- corresponding possible defined attribute function (e.g. for the
360 -- Read attribute, Nam will be TSS_Stream_Read).
362 procedure Check_System_Prefix;
363 -- Verify that prefix of attribute N is package System
365 procedure Check_PolyORB_Attribute;
366 -- Validity checking for PolyORB/DSA attribute
368 procedure Check_Task_Prefix;
369 -- Verify that prefix of attribute N is a task or task type
371 procedure Check_Type;
372 -- Verify that the prefix of attribute N is a type
374 procedure Check_Unit_Name (Nod : Node_Id);
375 -- Check that Nod is of the form of a library unit name, i.e that
376 -- it is an identifier, or a selected component whose prefix is
377 -- itself of the form of a library unit name. Note that this is
378 -- quite different from Check_Program_Unit, since it only checks
379 -- the syntactic form of the name, not the semantic identity. This
380 -- is because it is used with attributes (Elab_Body, Elab_Spec,
381 -- UET_Address and Elaborated) which can refer to non-visible unit.
383 procedure Error_Attr (Msg : String; Error_Node : Node_Id);
384 pragma No_Return (Error_Attr);
385 procedure Error_Attr;
386 pragma No_Return (Error_Attr);
387 -- Posts error using Error_Msg_N at given node, sets type of attribute
388 -- node to Any_Type, and then raises Bad_Attribute to avoid any further
389 -- semantic processing. The message typically contains a % insertion
390 -- character which is replaced by the attribute name. The call with
391 -- no arguments is used when the caller has already generated the
392 -- required error messages.
394 procedure Error_Attr_P (Msg : String);
395 pragma No_Return (Error_Attr);
396 -- Like Error_Attr, but error is posted at the start of the prefix
398 function In_Refined_Post return Boolean;
399 -- Determine whether the current attribute appears in pragma
400 -- Refined_Post.
402 procedure Legal_Formal_Attribute;
403 -- Common processing for attributes Definite and Has_Discriminants.
404 -- Checks that prefix is generic indefinite formal type.
406 procedure Max_Alignment_For_Allocation_Max_Size_In_Storage_Elements;
407 -- Common processing for attributes Max_Alignment_For_Allocation and
408 -- Max_Size_In_Storage_Elements.
410 procedure Min_Max;
411 -- Common processing for attributes Max and Min
413 procedure Standard_Attribute (Val : Int);
414 -- Used to process attributes whose prefix is package Standard which
415 -- yield values of type Universal_Integer. The attribute reference
416 -- node is rewritten with an integer literal of the given value which
417 -- is marked as static.
419 procedure Uneval_Old_Msg;
420 -- Called when Loop_Entry or Old is used in a potentially unevaluated
421 -- expression. Generates appropriate message or warning depending on
422 -- the setting of Opt.Uneval_Old (or flags in an N_Aspect_Specification
423 -- node in the aspect case).
425 procedure Unexpected_Argument (En : Node_Id);
426 -- Signal unexpected attribute argument (En is the argument)
428 procedure Validate_Non_Static_Attribute_Function_Call;
429 -- Called when processing an attribute that is a function call to a
430 -- non-static function, i.e. an attribute function that either takes
431 -- non-scalar arguments or returns a non-scalar result. Verifies that
432 -- such a call does not appear in a preelaborable context.
434 --------------------
435 -- Address_Checks --
436 --------------------
438 procedure Address_Checks is
439 begin
440 -- An Address attribute created by expansion is legal even when it
441 -- applies to other entity-denoting expressions.
443 if not Comes_From_Source (N) then
444 return;
446 -- Address attribute on a protected object self reference is legal
448 elsif Is_Protected_Self_Reference (P) then
449 return;
451 -- Address applied to an entity
453 elsif Is_Entity_Name (P) then
454 declare
455 Ent : constant Entity_Id := Entity (P);
457 begin
458 if Is_Subprogram (Ent) then
459 Set_Address_Taken (Ent);
460 Kill_Current_Values (Ent);
462 -- An Address attribute is accepted when generated by the
463 -- compiler for dispatching operation, and an error is
464 -- issued once the subprogram is frozen (to avoid confusing
465 -- errors about implicit uses of Address in the dispatch
466 -- table initialization).
468 if Has_Pragma_Inline_Always (Entity (P))
469 and then Comes_From_Source (P)
470 then
471 Error_Attr_P
472 ("prefix of % attribute cannot be Inline_Always "
473 & "subprogram");
475 -- It is illegal to apply 'Address to an intrinsic
476 -- subprogram. This is now formalized in AI05-0095.
477 -- In an instance, an attempt to obtain 'Address of an
478 -- intrinsic subprogram (e.g the renaming of a predefined
479 -- operator that is an actual) raises Program_Error.
481 elsif Convention (Ent) = Convention_Intrinsic then
482 if In_Instance then
483 Rewrite (N,
484 Make_Raise_Program_Error (Loc,
485 Reason => PE_Address_Of_Intrinsic));
487 else
488 Error_Msg_Name_1 := Aname;
489 Error_Msg_N
490 ("cannot take % of intrinsic subprogram", N);
491 end if;
493 -- Issue an error if prefix denotes an eliminated subprogram
495 else
496 Check_For_Eliminated_Subprogram (P, Ent);
497 end if;
499 -- Object or label reference
501 elsif Is_Object (Ent) or else Ekind (Ent) = E_Label then
502 Set_Address_Taken (Ent);
504 -- Deal with No_Implicit_Aliasing restriction
506 if Restriction_Check_Required (No_Implicit_Aliasing) then
507 if not Is_Aliased_View (P) then
508 Check_Restriction (No_Implicit_Aliasing, P);
509 else
510 Check_No_Implicit_Aliasing (P);
511 end if;
512 end if;
514 -- If we have an address of an object, and the attribute
515 -- comes from source, then set the object as potentially
516 -- source modified. We do this because the resulting address
517 -- can potentially be used to modify the variable and we
518 -- might not detect this, leading to some junk warnings.
520 Set_Never_Set_In_Source (Ent, False);
522 -- Allow Address to be applied to task or protected type,
523 -- returning null address (what is that about???)
525 elsif (Is_Concurrent_Type (Etype (Ent))
526 and then Etype (Ent) = Base_Type (Ent))
527 or else Ekind (Ent) = E_Package
528 or else Is_Generic_Unit (Ent)
529 then
530 Rewrite (N,
531 New_Occurrence_Of (RTE (RE_Null_Address), Sloc (N)));
533 -- Anything else is illegal
535 else
536 Error_Attr ("invalid prefix for % attribute", P);
537 end if;
538 end;
540 -- Object is OK
542 elsif Is_Object_Reference (P) then
543 return;
545 -- Subprogram called using dot notation
547 elsif Nkind (P) = N_Selected_Component
548 and then Is_Subprogram (Entity (Selector_Name (P)))
549 then
550 return;
552 -- What exactly are we allowing here ??? and is this properly
553 -- documented in the sinfo documentation for this node ???
555 elsif Relaxed_RM_Semantics
556 and then Nkind (P) = N_Attribute_Reference
557 then
558 return;
560 -- All other non-entity name cases are illegal
562 else
563 Error_Attr ("invalid prefix for % attribute", P);
564 end if;
565 end Address_Checks;
567 ------------------------------
568 -- Analyze_Access_Attribute --
569 ------------------------------
571 procedure Analyze_Access_Attribute is
572 Acc_Type : Entity_Id;
574 Scop : Entity_Id;
575 Typ : Entity_Id;
577 function Build_Access_Object_Type (DT : Entity_Id) return Entity_Id;
578 -- Build an access-to-object type whose designated type is DT,
579 -- and whose Ekind is appropriate to the attribute type. The
580 -- type that is constructed is returned as the result.
582 procedure Build_Access_Subprogram_Type (P : Node_Id);
583 -- Build an access to subprogram whose designated type is the type of
584 -- the prefix. If prefix is overloaded, so is the node itself. The
585 -- result is stored in Acc_Type.
587 function OK_Self_Reference return Boolean;
588 -- An access reference whose prefix is a type can legally appear
589 -- within an aggregate, where it is obtained by expansion of
590 -- a defaulted aggregate. The enclosing aggregate that contains
591 -- the self-referenced is flagged so that the self-reference can
592 -- be expanded into a reference to the target object (see exp_aggr).
594 ------------------------------
595 -- Build_Access_Object_Type --
596 ------------------------------
598 function Build_Access_Object_Type (DT : Entity_Id) return Entity_Id is
599 Typ : constant Entity_Id :=
600 New_Internal_Entity
601 (E_Access_Attribute_Type, Current_Scope, Loc, 'A');
602 begin
603 Set_Etype (Typ, Typ);
604 Set_Is_Itype (Typ);
605 Set_Associated_Node_For_Itype (Typ, N);
606 Set_Directly_Designated_Type (Typ, DT);
607 return Typ;
608 end Build_Access_Object_Type;
610 ----------------------------------
611 -- Build_Access_Subprogram_Type --
612 ----------------------------------
614 procedure Build_Access_Subprogram_Type (P : Node_Id) is
615 Index : Interp_Index;
616 It : Interp;
618 procedure Check_Local_Access (E : Entity_Id);
619 -- Deal with possible access to local subprogram. If we have such
620 -- an access, we set a flag to kill all tracked values on any call
621 -- because this access value may be passed around, and any called
622 -- code might use it to access a local procedure which clobbers a
623 -- tracked value. If the scope is a loop or block, indicate that
624 -- value tracking is disabled for the enclosing subprogram.
626 function Get_Kind (E : Entity_Id) return Entity_Kind;
627 -- Distinguish between access to regular/protected subprograms
629 ------------------------
630 -- Check_Local_Access --
631 ------------------------
633 procedure Check_Local_Access (E : Entity_Id) is
634 begin
635 if not Is_Library_Level_Entity (E) then
636 Set_Suppress_Value_Tracking_On_Call (Current_Scope);
637 Set_Suppress_Value_Tracking_On_Call
638 (Nearest_Dynamic_Scope (Current_Scope));
639 end if;
640 end Check_Local_Access;
642 --------------
643 -- Get_Kind --
644 --------------
646 function Get_Kind (E : Entity_Id) return Entity_Kind is
647 begin
648 if Convention (E) = Convention_Protected then
649 return E_Access_Protected_Subprogram_Type;
650 else
651 return E_Access_Subprogram_Type;
652 end if;
653 end Get_Kind;
655 -- Start of processing for Build_Access_Subprogram_Type
657 begin
658 -- In the case of an access to subprogram, use the name of the
659 -- subprogram itself as the designated type. Type-checking in
660 -- this case compares the signatures of the designated types.
662 -- Note: This fragment of the tree is temporarily malformed
663 -- because the correct tree requires an E_Subprogram_Type entity
664 -- as the designated type. In most cases this designated type is
665 -- later overridden by the semantics with the type imposed by the
666 -- context during the resolution phase. In the specific case of
667 -- the expression Address!(Prim'Unrestricted_Access), used to
668 -- initialize slots of dispatch tables, this work will be done by
669 -- the expander (see Exp_Aggr).
671 -- The reason to temporarily add this kind of node to the tree
672 -- instead of a proper E_Subprogram_Type itype, is the following:
673 -- in case of errors found in the source file we report better
674 -- error messages. For example, instead of generating the
675 -- following error:
677 -- "expected access to subprogram with profile
678 -- defined at line X"
680 -- we currently generate:
682 -- "expected access to function Z defined at line X"
684 Set_Etype (N, Any_Type);
686 if not Is_Overloaded (P) then
687 Check_Local_Access (Entity (P));
689 if not Is_Intrinsic_Subprogram (Entity (P)) then
690 Acc_Type := Create_Itype (Get_Kind (Entity (P)), N);
691 Set_Is_Public (Acc_Type, False);
692 Set_Etype (Acc_Type, Acc_Type);
693 Set_Convention (Acc_Type, Convention (Entity (P)));
694 Set_Directly_Designated_Type (Acc_Type, Entity (P));
695 Set_Etype (N, Acc_Type);
696 Freeze_Before (N, Acc_Type);
697 end if;
699 else
700 Get_First_Interp (P, Index, It);
701 while Present (It.Nam) loop
702 Check_Local_Access (It.Nam);
704 if not Is_Intrinsic_Subprogram (It.Nam) then
705 Acc_Type := Create_Itype (Get_Kind (It.Nam), N);
706 Set_Is_Public (Acc_Type, False);
707 Set_Etype (Acc_Type, Acc_Type);
708 Set_Convention (Acc_Type, Convention (It.Nam));
709 Set_Directly_Designated_Type (Acc_Type, It.Nam);
710 Add_One_Interp (N, Acc_Type, Acc_Type);
711 Freeze_Before (N, Acc_Type);
712 end if;
714 Get_Next_Interp (Index, It);
715 end loop;
716 end if;
718 -- Cannot be applied to intrinsic. Looking at the tests above,
719 -- the only way Etype (N) can still be set to Any_Type is if
720 -- Is_Intrinsic_Subprogram was True for some referenced entity.
722 if Etype (N) = Any_Type then
723 Error_Attr_P ("prefix of % attribute cannot be intrinsic");
724 end if;
725 end Build_Access_Subprogram_Type;
727 ----------------------
728 -- OK_Self_Reference --
729 ----------------------
731 function OK_Self_Reference return Boolean is
732 Par : Node_Id;
734 begin
735 Par := Parent (N);
736 while Present (Par)
737 and then
738 (Nkind (Par) = N_Component_Association
739 or else Nkind (Par) in N_Subexpr)
740 loop
741 if Nkind_In (Par, N_Aggregate, N_Extension_Aggregate) then
742 if Etype (Par) = Typ then
743 Set_Has_Self_Reference (Par);
744 return True;
745 end if;
746 end if;
748 Par := Parent (Par);
749 end loop;
751 -- No enclosing aggregate, or not a self-reference
753 return False;
754 end OK_Self_Reference;
756 -- Start of processing for Analyze_Access_Attribute
758 begin
759 Check_SPARK_05_Restriction_On_Attribute;
760 Check_E0;
762 if Nkind (P) = N_Character_Literal then
763 Error_Attr_P
764 ("prefix of % attribute cannot be enumeration literal");
765 end if;
767 -- Case of access to subprogram
769 if Is_Entity_Name (P) and then Is_Overloadable (Entity (P)) then
770 if Has_Pragma_Inline_Always (Entity (P)) then
771 Error_Attr_P
772 ("prefix of % attribute cannot be Inline_Always subprogram");
774 elsif Aname = Name_Unchecked_Access then
775 Error_Attr ("attribute% cannot be applied to a subprogram", P);
777 elsif Is_Ghost_Subprogram (Entity (P)) then
778 Error_Attr_P
779 ("prefix of % attribute cannot be a ghost subprogram");
780 end if;
782 -- Issue an error if the prefix denotes an eliminated subprogram
784 Check_For_Eliminated_Subprogram (P, Entity (P));
786 -- Check for obsolescent subprogram reference
788 Check_Obsolescent_2005_Entity (Entity (P), P);
790 -- Build the appropriate subprogram type
792 Build_Access_Subprogram_Type (P);
794 -- For P'Access or P'Unrestricted_Access, where P is a nested
795 -- subprogram, we might be passing P to another subprogram (but we
796 -- don't check that here), which might call P. P could modify
797 -- local variables, so we need to kill current values. It is
798 -- important not to do this for library-level subprograms, because
799 -- Kill_Current_Values is very inefficient in the case of library
800 -- level packages with lots of tagged types.
802 if Is_Library_Level_Entity (Entity (Prefix (N))) then
803 null;
805 -- Do not kill values on nodes initializing dispatch tables
806 -- slots. The construct Prim_Ptr!(Prim'Unrestricted_Access)
807 -- is currently generated by the expander only for this
808 -- purpose. Done to keep the quality of warnings currently
809 -- generated by the compiler (otherwise any declaration of
810 -- a tagged type cleans constant indications from its scope).
812 elsif Nkind (Parent (N)) = N_Unchecked_Type_Conversion
813 and then (Etype (Parent (N)) = RTE (RE_Prim_Ptr)
814 or else
815 Etype (Parent (N)) = RTE (RE_Size_Ptr))
816 and then Is_Dispatching_Operation
817 (Directly_Designated_Type (Etype (N)))
818 then
819 null;
821 else
822 Kill_Current_Values;
823 end if;
825 -- In the static elaboration model, treat the attribute reference
826 -- as a call for elaboration purposes. Suppress this treatment
827 -- under debug flag. In any case, we are all done.
829 if not Dynamic_Elaboration_Checks and not Debug_Flag_Dot_UU then
830 Check_Elab_Call (N);
831 end if;
833 return;
835 -- Component is an operation of a protected type
837 elsif Nkind (P) = N_Selected_Component
838 and then Is_Overloadable (Entity (Selector_Name (P)))
839 then
840 if Ekind (Entity (Selector_Name (P))) = E_Entry then
841 Error_Attr_P ("prefix of % attribute must be subprogram");
842 end if;
844 Build_Access_Subprogram_Type (Selector_Name (P));
845 return;
846 end if;
848 -- Deal with incorrect reference to a type, but note that some
849 -- accesses are allowed: references to the current type instance,
850 -- or in Ada 2005 self-referential pointer in a default-initialized
851 -- aggregate.
853 if Is_Entity_Name (P) then
854 Typ := Entity (P);
856 -- The reference may appear in an aggregate that has been expanded
857 -- into a loop. Locate scope of type definition, if any.
859 Scop := Current_Scope;
860 while Ekind (Scop) = E_Loop loop
861 Scop := Scope (Scop);
862 end loop;
864 if Is_Type (Typ) then
866 -- OK if we are within the scope of a limited type
867 -- let's mark the component as having per object constraint
869 if Is_Anonymous_Tagged_Base (Scop, Typ) then
870 Typ := Scop;
871 Set_Entity (P, Typ);
872 Set_Etype (P, Typ);
873 end if;
875 if Typ = Scop then
876 declare
877 Q : Node_Id := Parent (N);
879 begin
880 while Present (Q)
881 and then Nkind (Q) /= N_Component_Declaration
882 loop
883 Q := Parent (Q);
884 end loop;
886 if Present (Q) then
887 Set_Has_Per_Object_Constraint
888 (Defining_Identifier (Q), True);
889 end if;
890 end;
892 if Nkind (P) = N_Expanded_Name then
893 Error_Msg_F
894 ("current instance prefix must be a direct name", P);
895 end if;
897 -- If a current instance attribute appears in a component
898 -- constraint it must appear alone; other contexts (spec-
899 -- expressions, within a task body) are not subject to this
900 -- restriction.
902 if not In_Spec_Expression
903 and then not Has_Completion (Scop)
904 and then not
905 Nkind_In (Parent (N), N_Discriminant_Association,
906 N_Index_Or_Discriminant_Constraint)
907 then
908 Error_Msg_N
909 ("current instance attribute must appear alone", N);
910 end if;
912 if Is_CPP_Class (Root_Type (Typ)) then
913 Error_Msg_N
914 ("??current instance unsupported for derivations of "
915 & "'C'P'P types", N);
916 end if;
918 -- OK if we are in initialization procedure for the type
919 -- in question, in which case the reference to the type
920 -- is rewritten as a reference to the current object.
922 elsif Ekind (Scop) = E_Procedure
923 and then Is_Init_Proc (Scop)
924 and then Etype (First_Formal (Scop)) = Typ
925 then
926 Rewrite (N,
927 Make_Attribute_Reference (Loc,
928 Prefix => Make_Identifier (Loc, Name_uInit),
929 Attribute_Name => Name_Unrestricted_Access));
930 Analyze (N);
931 return;
933 -- OK if a task type, this test needs sharpening up ???
935 elsif Is_Task_Type (Typ) then
936 null;
938 -- OK if self-reference in an aggregate in Ada 2005, and
939 -- the reference comes from a copied default expression.
941 -- Note that we check legality of self-reference even if the
942 -- expression comes from source, e.g. when a single component
943 -- association in an aggregate has a box association.
945 elsif Ada_Version >= Ada_2005
946 and then OK_Self_Reference
947 then
948 null;
950 -- OK if reference to current instance of a protected object
952 elsif Is_Protected_Self_Reference (P) then
953 null;
955 -- Otherwise we have an error case
957 else
958 Error_Attr ("% attribute cannot be applied to type", P);
959 return;
960 end if;
961 end if;
962 end if;
964 -- If we fall through, we have a normal access to object case
966 -- Unrestricted_Access is (for now) legal wherever an allocator would
967 -- be legal, so its Etype is set to E_Allocator. The expected type
968 -- of the other attributes is a general access type, and therefore
969 -- we label them with E_Access_Attribute_Type.
971 if not Is_Overloaded (P) then
972 Acc_Type := Build_Access_Object_Type (P_Type);
973 Set_Etype (N, Acc_Type);
975 else
976 declare
977 Index : Interp_Index;
978 It : Interp;
979 begin
980 Set_Etype (N, Any_Type);
981 Get_First_Interp (P, Index, It);
982 while Present (It.Typ) loop
983 Acc_Type := Build_Access_Object_Type (It.Typ);
984 Add_One_Interp (N, Acc_Type, Acc_Type);
985 Get_Next_Interp (Index, It);
986 end loop;
987 end;
988 end if;
990 -- Special cases when we can find a prefix that is an entity name
992 declare
993 PP : Node_Id;
994 Ent : Entity_Id;
996 begin
997 PP := P;
998 loop
999 if Is_Entity_Name (PP) then
1000 Ent := Entity (PP);
1002 -- If we have an access to an object, and the attribute
1003 -- comes from source, then set the object as potentially
1004 -- source modified. We do this because the resulting access
1005 -- pointer can be used to modify the variable, and we might
1006 -- not detect this, leading to some junk warnings.
1008 -- We only do this for source references, since otherwise
1009 -- we can suppress warnings, e.g. from the unrestricted
1010 -- access generated for validity checks in -gnatVa mode.
1012 if Comes_From_Source (N) then
1013 Set_Never_Set_In_Source (Ent, False);
1014 end if;
1016 -- Mark entity as address taken, and kill current values
1018 Set_Address_Taken (Ent);
1019 Kill_Current_Values (Ent);
1020 exit;
1022 elsif Nkind_In (PP, N_Selected_Component,
1023 N_Indexed_Component)
1024 then
1025 PP := Prefix (PP);
1027 else
1028 exit;
1029 end if;
1030 end loop;
1031 end;
1033 -- Check for aliased view.. We allow a nonaliased prefix when within
1034 -- an instance because the prefix may have been a tagged formal
1035 -- object, which is defined to be aliased even when the actual
1036 -- might not be (other instance cases will have been caught in the
1037 -- generic). Similarly, within an inlined body we know that the
1038 -- attribute is legal in the original subprogram, and therefore
1039 -- legal in the expansion.
1041 if not Is_Aliased_View (P)
1042 and then not In_Instance
1043 and then not In_Inlined_Body
1044 then
1045 -- Here we have a non-aliased view. This is illegal unless we
1046 -- have the case of Unrestricted_Access, where for now we allow
1047 -- this (we will reject later if expected type is access to an
1048 -- unconstrained array with a thin pointer).
1050 if Aname /= Name_Unrestricted_Access then
1051 Error_Attr_P ("prefix of % attribute must be aliased");
1052 Check_No_Implicit_Aliasing (P);
1054 -- For Unrestricted_Access, record that prefix is not aliased
1055 -- to simplify legality check later on.
1057 else
1058 Set_Non_Aliased_Prefix (N);
1059 end if;
1061 -- If we have an aliased view, and we have Unrestricted_Access, then
1062 -- output a warning that Unchecked_Access would have been fine, and
1063 -- change the node to be Unchecked_Access.
1065 else
1066 -- For now, hold off on this change ???
1068 null;
1069 end if;
1070 end Analyze_Access_Attribute;
1072 ---------------------------------
1073 -- Bad_Attribute_For_Predicate --
1074 ---------------------------------
1076 procedure Bad_Attribute_For_Predicate is
1077 begin
1078 if Is_Scalar_Type (P_Type)
1079 and then Comes_From_Source (N)
1080 then
1081 Error_Msg_Name_1 := Aname;
1082 Bad_Predicated_Subtype_Use
1083 ("type& has predicates, attribute % not allowed", N, P_Type);
1084 end if;
1085 end Bad_Attribute_For_Predicate;
1087 --------------------------------
1088 -- Check_Array_Or_Scalar_Type --
1089 --------------------------------
1091 procedure Check_Array_Or_Scalar_Type is
1092 Index : Entity_Id;
1094 D : Int;
1095 -- Dimension number for array attributes
1097 begin
1098 -- Case of string literal or string literal subtype. These cases
1099 -- cannot arise from legal Ada code, but the expander is allowed
1100 -- to generate them. They require special handling because string
1101 -- literal subtypes do not have standard bounds (the whole idea
1102 -- of these subtypes is to avoid having to generate the bounds)
1104 if Ekind (P_Type) = E_String_Literal_Subtype then
1105 Set_Etype (N, Etype (First_Index (P_Base_Type)));
1106 return;
1108 -- Scalar types
1110 elsif Is_Scalar_Type (P_Type) then
1111 Check_Type;
1113 if Present (E1) then
1114 Error_Attr ("invalid argument in % attribute", E1);
1115 else
1116 Set_Etype (N, P_Base_Type);
1117 return;
1118 end if;
1120 -- The following is a special test to allow 'First to apply to
1121 -- private scalar types if the attribute comes from generated
1122 -- code. This occurs in the case of Normalize_Scalars code.
1124 elsif Is_Private_Type (P_Type)
1125 and then Present (Full_View (P_Type))
1126 and then Is_Scalar_Type (Full_View (P_Type))
1127 and then not Comes_From_Source (N)
1128 then
1129 Set_Etype (N, Implementation_Base_Type (P_Type));
1131 -- Array types other than string literal subtypes handled above
1133 else
1134 Check_Array_Type;
1136 -- We know prefix is an array type, or the name of an array
1137 -- object, and that the expression, if present, is static
1138 -- and within the range of the dimensions of the type.
1140 pragma Assert (Is_Array_Type (P_Type));
1141 Index := First_Index (P_Base_Type);
1143 if No (E1) then
1145 -- First dimension assumed
1147 Set_Etype (N, Base_Type (Etype (Index)));
1149 else
1150 D := UI_To_Int (Intval (E1));
1152 for J in 1 .. D - 1 loop
1153 Next_Index (Index);
1154 end loop;
1156 Set_Etype (N, Base_Type (Etype (Index)));
1157 Set_Etype (E1, Standard_Integer);
1158 end if;
1159 end if;
1160 end Check_Array_Or_Scalar_Type;
1162 ----------------------
1163 -- Check_Array_Type --
1164 ----------------------
1166 procedure Check_Array_Type is
1167 D : Int;
1168 -- Dimension number for array attributes
1170 begin
1171 -- If the type is a string literal type, then this must be generated
1172 -- internally, and no further check is required on its legality.
1174 if Ekind (P_Type) = E_String_Literal_Subtype then
1175 return;
1177 -- If the type is a composite, it is an illegal aggregate, no point
1178 -- in going on.
1180 elsif P_Type = Any_Composite then
1181 raise Bad_Attribute;
1182 end if;
1184 -- Normal case of array type or subtype
1186 Check_Either_E0_Or_E1;
1187 Check_Dereference;
1189 if Is_Array_Type (P_Type) then
1190 if not Is_Constrained (P_Type)
1191 and then Is_Entity_Name (P)
1192 and then Is_Type (Entity (P))
1193 then
1194 -- Note: we do not call Error_Attr here, since we prefer to
1195 -- continue, using the relevant index type of the array,
1196 -- even though it is unconstrained. This gives better error
1197 -- recovery behavior.
1199 Error_Msg_Name_1 := Aname;
1200 Error_Msg_F
1201 ("prefix for % attribute must be constrained array", P);
1202 end if;
1204 -- The attribute reference freezes the type, and thus the
1205 -- component type, even if the attribute may not depend on the
1206 -- component. Diagnose arrays with incomplete components now.
1207 -- If the prefix is an access to array, this does not freeze
1208 -- the designated type.
1210 if Nkind (P) /= N_Explicit_Dereference then
1211 Check_Fully_Declared (Component_Type (P_Type), P);
1212 end if;
1214 D := Number_Dimensions (P_Type);
1216 else
1217 if Is_Private_Type (P_Type) then
1218 Error_Attr_P ("prefix for % attribute may not be private type");
1220 elsif Is_Access_Type (P_Type)
1221 and then Is_Array_Type (Designated_Type (P_Type))
1222 and then Is_Entity_Name (P)
1223 and then Is_Type (Entity (P))
1224 then
1225 Error_Attr_P ("prefix of % attribute cannot be access type");
1227 elsif Attr_Id = Attribute_First
1228 or else
1229 Attr_Id = Attribute_Last
1230 then
1231 Error_Attr ("invalid prefix for % attribute", P);
1233 else
1234 Error_Attr_P ("prefix for % attribute must be array");
1235 end if;
1236 end if;
1238 if Present (E1) then
1239 Resolve (E1, Any_Integer);
1240 Set_Etype (E1, Standard_Integer);
1242 if not Is_OK_Static_Expression (E1)
1243 or else Raises_Constraint_Error (E1)
1244 then
1245 Flag_Non_Static_Expr
1246 ("expression for dimension must be static!", E1);
1247 Error_Attr;
1249 elsif UI_To_Int (Expr_Value (E1)) > D
1250 or else UI_To_Int (Expr_Value (E1)) < 1
1251 then
1252 Error_Attr ("invalid dimension number for array type", E1);
1253 end if;
1254 end if;
1256 if (Style_Check and Style_Check_Array_Attribute_Index)
1257 and then Comes_From_Source (N)
1258 then
1259 Style.Check_Array_Attribute_Index (N, E1, D);
1260 end if;
1261 end Check_Array_Type;
1263 -------------------------
1264 -- Check_Asm_Attribute --
1265 -------------------------
1267 procedure Check_Asm_Attribute is
1268 begin
1269 Check_Type;
1270 Check_E2;
1272 -- Check first argument is static string expression
1274 Analyze_And_Resolve (E1, Standard_String);
1276 if Etype (E1) = Any_Type then
1277 return;
1279 elsif not Is_OK_Static_Expression (E1) then
1280 Flag_Non_Static_Expr
1281 ("constraint argument must be static string expression!", E1);
1282 Error_Attr;
1283 end if;
1285 -- Check second argument is right type
1287 Analyze_And_Resolve (E2, Entity (P));
1289 -- Note: that is all we need to do, we don't need to check
1290 -- that it appears in a correct context. The Ada type system
1291 -- will do that for us.
1293 end Check_Asm_Attribute;
1295 ---------------------
1296 -- Check_Component --
1297 ---------------------
1299 procedure Check_Component is
1300 begin
1301 Check_E0;
1303 if Nkind (P) /= N_Selected_Component
1304 or else
1305 (Ekind (Entity (Selector_Name (P))) /= E_Component
1306 and then
1307 Ekind (Entity (Selector_Name (P))) /= E_Discriminant)
1308 then
1309 Error_Attr_P ("prefix for % attribute must be selected component");
1310 end if;
1311 end Check_Component;
1313 ------------------------------------
1314 -- Check_Decimal_Fixed_Point_Type --
1315 ------------------------------------
1317 procedure Check_Decimal_Fixed_Point_Type is
1318 begin
1319 Check_Type;
1321 if not Is_Decimal_Fixed_Point_Type (P_Type) then
1322 Error_Attr_P ("prefix of % attribute must be decimal type");
1323 end if;
1324 end Check_Decimal_Fixed_Point_Type;
1326 -----------------------
1327 -- Check_Dereference --
1328 -----------------------
1330 procedure Check_Dereference is
1331 begin
1333 -- Case of a subtype mark
1335 if Is_Entity_Name (P) and then Is_Type (Entity (P)) then
1336 return;
1337 end if;
1339 -- Case of an expression
1341 Resolve (P);
1343 if Is_Access_Type (P_Type) then
1345 -- If there is an implicit dereference, then we must freeze the
1346 -- designated type of the access type, since the type of the
1347 -- referenced array is this type (see AI95-00106).
1349 -- As done elsewhere, freezing must not happen when pre-analyzing
1350 -- a pre- or postcondition or a default value for an object or for
1351 -- a formal parameter.
1353 if not In_Spec_Expression then
1354 Freeze_Before (N, Designated_Type (P_Type));
1355 end if;
1357 Rewrite (P,
1358 Make_Explicit_Dereference (Sloc (P),
1359 Prefix => Relocate_Node (P)));
1361 Analyze_And_Resolve (P);
1362 P_Type := Etype (P);
1364 if P_Type = Any_Type then
1365 raise Bad_Attribute;
1366 end if;
1368 P_Base_Type := Base_Type (P_Type);
1369 end if;
1370 end Check_Dereference;
1372 -------------------------
1373 -- Check_Discrete_Type --
1374 -------------------------
1376 procedure Check_Discrete_Type is
1377 begin
1378 Check_Type;
1380 if not Is_Discrete_Type (P_Type) then
1381 Error_Attr_P ("prefix of % attribute must be discrete type");
1382 end if;
1383 end Check_Discrete_Type;
1385 --------------
1386 -- Check_E0 --
1387 --------------
1389 procedure Check_E0 is
1390 begin
1391 if Present (E1) then
1392 Unexpected_Argument (E1);
1393 end if;
1394 end Check_E0;
1396 --------------
1397 -- Check_E1 --
1398 --------------
1400 procedure Check_E1 is
1401 begin
1402 Check_Either_E0_Or_E1;
1404 if No (E1) then
1406 -- Special-case attributes that are functions and that appear as
1407 -- the prefix of another attribute. Error is posted on parent.
1409 if Nkind (Parent (N)) = N_Attribute_Reference
1410 and then Nam_In (Attribute_Name (Parent (N)), Name_Address,
1411 Name_Code_Address,
1412 Name_Access)
1413 then
1414 Error_Msg_Name_1 := Attribute_Name (Parent (N));
1415 Error_Msg_N ("illegal prefix for % attribute", Parent (N));
1416 Set_Etype (Parent (N), Any_Type);
1417 Set_Entity (Parent (N), Any_Type);
1418 raise Bad_Attribute;
1420 else
1421 Error_Attr ("missing argument for % attribute", N);
1422 end if;
1423 end if;
1424 end Check_E1;
1426 --------------
1427 -- Check_E2 --
1428 --------------
1430 procedure Check_E2 is
1431 begin
1432 if No (E1) then
1433 Error_Attr ("missing arguments for % attribute (2 required)", N);
1434 elsif No (E2) then
1435 Error_Attr ("missing argument for % attribute (2 required)", N);
1436 end if;
1437 end Check_E2;
1439 ---------------------------
1440 -- Check_Either_E0_Or_E1 --
1441 ---------------------------
1443 procedure Check_Either_E0_Or_E1 is
1444 begin
1445 if Present (E2) then
1446 Unexpected_Argument (E2);
1447 end if;
1448 end Check_Either_E0_Or_E1;
1450 ----------------------
1451 -- Check_Enum_Image --
1452 ----------------------
1454 procedure Check_Enum_Image is
1455 Lit : Entity_Id;
1457 begin
1458 -- When an enumeration type appears in an attribute reference, all
1459 -- literals of the type are marked as referenced. This must only be
1460 -- done if the attribute reference appears in the current source.
1461 -- Otherwise the information on references may differ between a
1462 -- normal compilation and one that performs inlining.
1464 if Is_Enumeration_Type (P_Base_Type)
1465 and then In_Extended_Main_Code_Unit (N)
1466 then
1467 Lit := First_Literal (P_Base_Type);
1468 while Present (Lit) loop
1469 Set_Referenced (Lit);
1470 Next_Literal (Lit);
1471 end loop;
1472 end if;
1473 end Check_Enum_Image;
1475 ----------------------------
1476 -- Check_First_Last_Valid --
1477 ----------------------------
1479 procedure Check_First_Last_Valid is
1480 begin
1481 Check_Discrete_Type;
1483 -- Freeze the subtype now, so that the following test for predicates
1484 -- works (we set the predicates stuff up at freeze time)
1486 Insert_Actions (N, Freeze_Entity (P_Type, P));
1488 -- Now test for dynamic predicate
1490 if Has_Predicates (P_Type)
1491 and then not (Has_Static_Predicate (P_Type))
1492 then
1493 Error_Attr_P
1494 ("prefix of % attribute may not have dynamic predicate");
1495 end if;
1497 -- Check non-static subtype
1499 if not Is_OK_Static_Subtype (P_Type) then
1500 Error_Attr_P ("prefix of % attribute must be a static subtype");
1501 end if;
1503 -- Test case for no values
1505 if Expr_Value (Type_Low_Bound (P_Type)) >
1506 Expr_Value (Type_High_Bound (P_Type))
1507 or else (Has_Predicates (P_Type)
1508 and then
1509 Is_Empty_List (Static_Discrete_Predicate (P_Type)))
1510 then
1511 Error_Attr_P
1512 ("prefix of % attribute must be subtype with "
1513 & "at least one value");
1514 end if;
1515 end Check_First_Last_Valid;
1517 ----------------------------
1518 -- Check_Fixed_Point_Type --
1519 ----------------------------
1521 procedure Check_Fixed_Point_Type is
1522 begin
1523 Check_Type;
1525 if not Is_Fixed_Point_Type (P_Type) then
1526 Error_Attr_P ("prefix of % attribute must be fixed point type");
1527 end if;
1528 end Check_Fixed_Point_Type;
1530 ------------------------------
1531 -- Check_Fixed_Point_Type_0 --
1532 ------------------------------
1534 procedure Check_Fixed_Point_Type_0 is
1535 begin
1536 Check_Fixed_Point_Type;
1537 Check_E0;
1538 end Check_Fixed_Point_Type_0;
1540 -------------------------------
1541 -- Check_Floating_Point_Type --
1542 -------------------------------
1544 procedure Check_Floating_Point_Type is
1545 begin
1546 Check_Type;
1548 if not Is_Floating_Point_Type (P_Type) then
1549 Error_Attr_P ("prefix of % attribute must be float type");
1550 end if;
1551 end Check_Floating_Point_Type;
1553 ---------------------------------
1554 -- Check_Floating_Point_Type_0 --
1555 ---------------------------------
1557 procedure Check_Floating_Point_Type_0 is
1558 begin
1559 Check_Floating_Point_Type;
1560 Check_E0;
1561 end Check_Floating_Point_Type_0;
1563 ---------------------------------
1564 -- Check_Floating_Point_Type_1 --
1565 ---------------------------------
1567 procedure Check_Floating_Point_Type_1 is
1568 begin
1569 Check_Floating_Point_Type;
1570 Check_E1;
1571 end Check_Floating_Point_Type_1;
1573 ---------------------------------
1574 -- Check_Floating_Point_Type_2 --
1575 ---------------------------------
1577 procedure Check_Floating_Point_Type_2 is
1578 begin
1579 Check_Floating_Point_Type;
1580 Check_E2;
1581 end Check_Floating_Point_Type_2;
1583 ------------------------
1584 -- Check_Integer_Type --
1585 ------------------------
1587 procedure Check_Integer_Type is
1588 begin
1589 Check_Type;
1591 if not Is_Integer_Type (P_Type) then
1592 Error_Attr_P ("prefix of % attribute must be integer type");
1593 end if;
1594 end Check_Integer_Type;
1596 --------------------------------
1597 -- Check_Modular_Integer_Type --
1598 --------------------------------
1600 procedure Check_Modular_Integer_Type is
1601 begin
1602 Check_Type;
1604 if not Is_Modular_Integer_Type (P_Type) then
1605 Error_Attr_P
1606 ("prefix of % attribute must be modular integer type");
1607 end if;
1608 end Check_Modular_Integer_Type;
1610 ------------------------
1611 -- Check_Not_CPP_Type --
1612 ------------------------
1614 procedure Check_Not_CPP_Type is
1615 begin
1616 if Is_Tagged_Type (Etype (P))
1617 and then Convention (Etype (P)) = Convention_CPP
1618 and then Is_CPP_Class (Root_Type (Etype (P)))
1619 then
1620 Error_Attr_P
1621 ("invalid use of % attribute with 'C'P'P tagged type");
1622 end if;
1623 end Check_Not_CPP_Type;
1625 -------------------------------
1626 -- Check_Not_Incomplete_Type --
1627 -------------------------------
1629 procedure Check_Not_Incomplete_Type is
1630 E : Entity_Id;
1631 Typ : Entity_Id;
1633 begin
1634 -- Ada 2005 (AI-50217, AI-326): If the prefix is an explicit
1635 -- dereference we have to check wrong uses of incomplete types
1636 -- (other wrong uses are checked at their freezing point).
1638 -- Example 1: Limited-with
1640 -- limited with Pkg;
1641 -- package P is
1642 -- type Acc is access Pkg.T;
1643 -- X : Acc;
1644 -- S : Integer := X.all'Size; -- ERROR
1645 -- end P;
1647 -- Example 2: Tagged incomplete
1649 -- type T is tagged;
1650 -- type Acc is access all T;
1651 -- X : Acc;
1652 -- S : constant Integer := X.all'Size; -- ERROR
1653 -- procedure Q (Obj : Integer := X.all'Alignment); -- ERROR
1655 if Ada_Version >= Ada_2005
1656 and then Nkind (P) = N_Explicit_Dereference
1657 then
1658 E := P;
1659 while Nkind (E) = N_Explicit_Dereference loop
1660 E := Prefix (E);
1661 end loop;
1663 Typ := Etype (E);
1665 if From_Limited_With (Typ) then
1666 Error_Attr_P
1667 ("prefix of % attribute cannot be an incomplete type");
1669 else
1670 if Is_Access_Type (Typ) then
1671 Typ := Directly_Designated_Type (Typ);
1672 end if;
1674 if Is_Class_Wide_Type (Typ) then
1675 Typ := Root_Type (Typ);
1676 end if;
1678 -- A legal use of a shadow entity occurs only when the unit
1679 -- where the non-limited view resides is imported via a regular
1680 -- with clause in the current body. Such references to shadow
1681 -- entities may occur in subprogram formals.
1683 if Is_Incomplete_Type (Typ)
1684 and then From_Limited_With (Typ)
1685 and then Present (Non_Limited_View (Typ))
1686 and then Is_Legal_Shadow_Entity_In_Body (Typ)
1687 then
1688 Typ := Non_Limited_View (Typ);
1689 end if;
1691 if Ekind (Typ) = E_Incomplete_Type
1692 and then No (Full_View (Typ))
1693 then
1694 Error_Attr_P
1695 ("prefix of % attribute cannot be an incomplete type");
1696 end if;
1697 end if;
1698 end if;
1700 if not Is_Entity_Name (P)
1701 or else not Is_Type (Entity (P))
1702 or else In_Spec_Expression
1703 then
1704 return;
1705 else
1706 Check_Fully_Declared (P_Type, P);
1707 end if;
1708 end Check_Not_Incomplete_Type;
1710 ----------------------------
1711 -- Check_Object_Reference --
1712 ----------------------------
1714 procedure Check_Object_Reference (P : Node_Id) is
1715 Rtyp : Entity_Id;
1717 begin
1718 -- If we need an object, and we have a prefix that is the name of
1719 -- a function entity, convert it into a function call.
1721 if Is_Entity_Name (P)
1722 and then Ekind (Entity (P)) = E_Function
1723 then
1724 Rtyp := Etype (Entity (P));
1726 Rewrite (P,
1727 Make_Function_Call (Sloc (P),
1728 Name => Relocate_Node (P)));
1730 Analyze_And_Resolve (P, Rtyp);
1732 -- Otherwise we must have an object reference
1734 elsif not Is_Object_Reference (P) then
1735 Error_Attr_P ("prefix of % attribute must be object");
1736 end if;
1737 end Check_Object_Reference;
1739 ----------------------------
1740 -- Check_PolyORB_Attribute --
1741 ----------------------------
1743 procedure Check_PolyORB_Attribute is
1744 begin
1745 Validate_Non_Static_Attribute_Function_Call;
1747 Check_Type;
1748 Check_Not_CPP_Type;
1750 if Get_PCS_Name /= Name_PolyORB_DSA then
1751 Error_Attr
1752 ("attribute% requires the 'Poly'O'R'B 'P'C'S", N);
1753 end if;
1754 end Check_PolyORB_Attribute;
1756 ------------------------
1757 -- Check_Program_Unit --
1758 ------------------------
1760 procedure Check_Program_Unit is
1761 begin
1762 if Is_Entity_Name (P) then
1763 declare
1764 K : constant Entity_Kind := Ekind (Entity (P));
1765 T : constant Entity_Id := Etype (Entity (P));
1767 begin
1768 if K in Subprogram_Kind
1769 or else K in Task_Kind
1770 or else K in Protected_Kind
1771 or else K = E_Package
1772 or else K in Generic_Unit_Kind
1773 or else (K = E_Variable
1774 and then
1775 (Is_Task_Type (T)
1776 or else
1777 Is_Protected_Type (T)))
1778 then
1779 return;
1780 end if;
1781 end;
1782 end if;
1784 Error_Attr_P ("prefix of % attribute must be program unit");
1785 end Check_Program_Unit;
1787 ---------------------
1788 -- Check_Real_Type --
1789 ---------------------
1791 procedure Check_Real_Type is
1792 begin
1793 Check_Type;
1795 if not Is_Real_Type (P_Type) then
1796 Error_Attr_P ("prefix of % attribute must be real type");
1797 end if;
1798 end Check_Real_Type;
1800 -----------------------
1801 -- Check_Scalar_Type --
1802 -----------------------
1804 procedure Check_Scalar_Type is
1805 begin
1806 Check_Type;
1808 if not Is_Scalar_Type (P_Type) then
1809 Error_Attr_P ("prefix of % attribute must be scalar type");
1810 end if;
1811 end Check_Scalar_Type;
1813 ------------------------------------------
1814 -- Check_SPARK_05_Restriction_On_Attribute --
1815 ------------------------------------------
1817 procedure Check_SPARK_05_Restriction_On_Attribute is
1818 begin
1819 Error_Msg_Name_1 := Aname;
1820 Check_SPARK_05_Restriction ("attribute % is not allowed", P);
1821 end Check_SPARK_05_Restriction_On_Attribute;
1823 ---------------------------
1824 -- Check_Standard_Prefix --
1825 ---------------------------
1827 procedure Check_Standard_Prefix is
1828 begin
1829 Check_E0;
1831 if Nkind (P) /= N_Identifier or else Chars (P) /= Name_Standard then
1832 Error_Attr ("only allowed prefix for % attribute is Standard", P);
1833 end if;
1834 end Check_Standard_Prefix;
1836 ----------------------------
1837 -- Check_Stream_Attribute --
1838 ----------------------------
1840 procedure Check_Stream_Attribute (Nam : TSS_Name_Type) is
1841 Etyp : Entity_Id;
1842 Btyp : Entity_Id;
1844 In_Shared_Var_Procs : Boolean;
1845 -- True when compiling System.Shared_Storage.Shared_Var_Procs body.
1846 -- For this runtime package (always compiled in GNAT mode), we allow
1847 -- stream attributes references for limited types for the case where
1848 -- shared passive objects are implemented using stream attributes,
1849 -- which is the default in GNAT's persistent storage implementation.
1851 begin
1852 Validate_Non_Static_Attribute_Function_Call;
1854 -- With the exception of 'Input, Stream attributes are procedures,
1855 -- and can only appear at the position of procedure calls. We check
1856 -- for this here, before they are rewritten, to give a more precise
1857 -- diagnostic.
1859 if Nam = TSS_Stream_Input then
1860 null;
1862 elsif Is_List_Member (N)
1863 and then not Nkind_In (Parent (N), N_Procedure_Call_Statement,
1864 N_Aggregate)
1865 then
1866 null;
1868 else
1869 Error_Attr
1870 ("invalid context for attribute%, which is a procedure", N);
1871 end if;
1873 Check_Type;
1874 Btyp := Implementation_Base_Type (P_Type);
1876 -- Stream attributes not allowed on limited types unless the
1877 -- attribute reference was generated by the expander (in which
1878 -- case the underlying type will be used, as described in Sinfo),
1879 -- or the attribute was specified explicitly for the type itself
1880 -- or one of its ancestors (taking visibility rules into account if
1881 -- in Ada 2005 mode), or a pragma Stream_Convert applies to Btyp
1882 -- (with no visibility restriction).
1884 declare
1885 Gen_Body : constant Node_Id := Enclosing_Generic_Body (N);
1886 begin
1887 if Present (Gen_Body) then
1888 In_Shared_Var_Procs :=
1889 Is_RTE (Corresponding_Spec (Gen_Body), RE_Shared_Var_Procs);
1890 else
1891 In_Shared_Var_Procs := False;
1892 end if;
1893 end;
1895 if (Comes_From_Source (N)
1896 and then not (In_Shared_Var_Procs or In_Instance))
1897 and then not Stream_Attribute_Available (P_Type, Nam)
1898 and then not Has_Rep_Pragma (Btyp, Name_Stream_Convert)
1899 then
1900 Error_Msg_Name_1 := Aname;
1902 if Is_Limited_Type (P_Type) then
1903 Error_Msg_NE
1904 ("limited type& has no% attribute", P, P_Type);
1905 Explain_Limited_Type (P_Type, P);
1906 else
1907 Error_Msg_NE
1908 ("attribute% for type& is not available", P, P_Type);
1909 end if;
1910 end if;
1912 -- Check restriction violations
1914 -- First check the No_Streams restriction, which prohibits the use
1915 -- of explicit stream attributes in the source program. We do not
1916 -- prevent the occurrence of stream attributes in generated code,
1917 -- for instance those generated implicitly for dispatching purposes.
1919 if Comes_From_Source (N) then
1920 Check_Restriction (No_Streams, P);
1921 end if;
1923 -- AI05-0057: if restriction No_Default_Stream_Attributes is active,
1924 -- it is illegal to use a predefined elementary type stream attribute
1925 -- either by itself, or more importantly as part of the attribute
1926 -- subprogram for a composite type. However, if the broader
1927 -- restriction No_Streams is active, stream operations are not
1928 -- generated, and there is no error.
1930 if Restriction_Active (No_Default_Stream_Attributes)
1931 and then not Restriction_Active (No_Streams)
1932 then
1933 declare
1934 T : Entity_Id;
1936 begin
1937 if Nam = TSS_Stream_Input
1938 or else
1939 Nam = TSS_Stream_Read
1940 then
1941 T :=
1942 Type_Without_Stream_Operation (P_Type, TSS_Stream_Read);
1943 else
1944 T :=
1945 Type_Without_Stream_Operation (P_Type, TSS_Stream_Write);
1946 end if;
1948 if Present (T) then
1949 Check_Restriction (No_Default_Stream_Attributes, N);
1951 Error_Msg_NE
1952 ("missing user-defined Stream Read or Write for type&",
1953 N, T);
1954 if not Is_Elementary_Type (P_Type) then
1955 Error_Msg_NE
1956 ("\which is a component of type&", N, P_Type);
1957 end if;
1958 end if;
1959 end;
1960 end if;
1962 -- Check special case of Exception_Id and Exception_Occurrence which
1963 -- are not allowed for restriction No_Exception_Registration.
1965 if Restriction_Check_Required (No_Exception_Registration)
1966 and then (Is_RTE (P_Type, RE_Exception_Id)
1967 or else
1968 Is_RTE (P_Type, RE_Exception_Occurrence))
1969 then
1970 Check_Restriction (No_Exception_Registration, P);
1971 end if;
1973 -- Here we must check that the first argument is an access type
1974 -- that is compatible with Ada.Streams.Root_Stream_Type'Class.
1976 Analyze_And_Resolve (E1);
1977 Etyp := Etype (E1);
1979 -- Note: the double call to Root_Type here is needed because the
1980 -- root type of a class-wide type is the corresponding type (e.g.
1981 -- X for X'Class, and we really want to go to the root.)
1983 if not Is_Access_Type (Etyp)
1984 or else Root_Type (Root_Type (Designated_Type (Etyp))) /=
1985 RTE (RE_Root_Stream_Type)
1986 then
1987 Error_Attr
1988 ("expected access to Ada.Streams.Root_Stream_Type''Class", E1);
1989 end if;
1991 -- Check that the second argument is of the right type if there is
1992 -- one (the Input attribute has only one argument so this is skipped)
1994 if Present (E2) then
1995 Analyze (E2);
1997 if Nam = TSS_Stream_Read
1998 and then not Is_OK_Variable_For_Out_Formal (E2)
1999 then
2000 Error_Attr
2001 ("second argument of % attribute must be a variable", E2);
2002 end if;
2004 Resolve (E2, P_Type);
2005 end if;
2007 Check_Not_CPP_Type;
2008 end Check_Stream_Attribute;
2010 -------------------------
2011 -- Check_System_Prefix --
2012 -------------------------
2014 procedure Check_System_Prefix is
2015 begin
2016 if Nkind (P) /= N_Identifier or else Chars (P) /= Name_System then
2017 Error_Attr ("only allowed prefix for % attribute is System", P);
2018 end if;
2019 end Check_System_Prefix;
2021 -----------------------
2022 -- Check_Task_Prefix --
2023 -----------------------
2025 procedure Check_Task_Prefix is
2026 begin
2027 Analyze (P);
2029 -- Ada 2005 (AI-345): Attribute 'Terminated can be applied to
2030 -- task interface class-wide types.
2032 if Is_Task_Type (Etype (P))
2033 or else (Is_Access_Type (Etype (P))
2034 and then Is_Task_Type (Designated_Type (Etype (P))))
2035 or else (Ada_Version >= Ada_2005
2036 and then Ekind (Etype (P)) = E_Class_Wide_Type
2037 and then Is_Interface (Etype (P))
2038 and then Is_Task_Interface (Etype (P)))
2039 then
2040 Resolve (P);
2042 else
2043 if Ada_Version >= Ada_2005 then
2044 Error_Attr_P
2045 ("prefix of % attribute must be a task or a task " &
2046 "interface class-wide object");
2048 else
2049 Error_Attr_P ("prefix of % attribute must be a task");
2050 end if;
2051 end if;
2052 end Check_Task_Prefix;
2054 ----------------
2055 -- Check_Type --
2056 ----------------
2058 -- The possibilities are an entity name denoting a type, or an
2059 -- attribute reference that denotes a type (Base or Class). If
2060 -- the type is incomplete, replace it with its full view.
2062 procedure Check_Type is
2063 begin
2064 if not Is_Entity_Name (P)
2065 or else not Is_Type (Entity (P))
2066 then
2067 Error_Attr_P ("prefix of % attribute must be a type");
2069 elsif Is_Protected_Self_Reference (P) then
2070 Error_Attr_P
2071 ("prefix of % attribute denotes current instance "
2072 & "(RM 9.4(21/2))");
2074 elsif Ekind (Entity (P)) = E_Incomplete_Type
2075 and then Present (Full_View (Entity (P)))
2076 then
2077 P_Type := Full_View (Entity (P));
2078 Set_Entity (P, P_Type);
2079 end if;
2080 end Check_Type;
2082 ---------------------
2083 -- Check_Unit_Name --
2084 ---------------------
2086 procedure Check_Unit_Name (Nod : Node_Id) is
2087 begin
2088 if Nkind (Nod) = N_Identifier then
2089 return;
2091 elsif Nkind_In (Nod, N_Selected_Component, N_Expanded_Name) then
2092 Check_Unit_Name (Prefix (Nod));
2094 if Nkind (Selector_Name (Nod)) = N_Identifier then
2095 return;
2096 end if;
2097 end if;
2099 Error_Attr ("argument for % attribute must be unit name", P);
2100 end Check_Unit_Name;
2102 ----------------
2103 -- Error_Attr --
2104 ----------------
2106 procedure Error_Attr is
2107 begin
2108 Set_Etype (N, Any_Type);
2109 Set_Entity (N, Any_Type);
2110 raise Bad_Attribute;
2111 end Error_Attr;
2113 procedure Error_Attr (Msg : String; Error_Node : Node_Id) is
2114 begin
2115 Error_Msg_Name_1 := Aname;
2116 Error_Msg_N (Msg, Error_Node);
2117 Error_Attr;
2118 end Error_Attr;
2120 ------------------
2121 -- Error_Attr_P --
2122 ------------------
2124 procedure Error_Attr_P (Msg : String) is
2125 begin
2126 Error_Msg_Name_1 := Aname;
2127 Error_Msg_F (Msg, P);
2128 Error_Attr;
2129 end Error_Attr_P;
2131 ---------------------
2132 -- In_Refined_Post --
2133 ---------------------
2135 function In_Refined_Post return Boolean is
2136 function Is_Refined_Post (Prag : Node_Id) return Boolean;
2137 -- Determine whether Prag denotes one of the incarnations of pragma
2138 -- Refined_Post (either as is or pragma Check (Refined_Post, ...).
2140 ---------------------
2141 -- Is_Refined_Post --
2142 ---------------------
2144 function Is_Refined_Post (Prag : Node_Id) return Boolean is
2145 Args : constant List_Id := Pragma_Argument_Associations (Prag);
2146 Nam : constant Name_Id := Pragma_Name (Prag);
2148 begin
2149 if Nam = Name_Refined_Post then
2150 return True;
2152 elsif Nam = Name_Check then
2153 pragma Assert (Present (Args));
2155 return Chars (Expression (First (Args))) = Name_Refined_Post;
2156 end if;
2158 return False;
2159 end Is_Refined_Post;
2161 -- Local variables
2163 Stmt : Node_Id;
2165 -- Start of processing for In_Refined_Post
2167 begin
2168 Stmt := Parent (N);
2169 while Present (Stmt) loop
2170 if Nkind (Stmt) = N_Pragma and then Is_Refined_Post (Stmt) then
2171 return True;
2173 -- Prevent the search from going too far
2175 elsif Is_Body_Or_Package_Declaration (Stmt) then
2176 exit;
2177 end if;
2179 Stmt := Parent (Stmt);
2180 end loop;
2182 return False;
2183 end In_Refined_Post;
2185 ----------------------------
2186 -- Legal_Formal_Attribute --
2187 ----------------------------
2189 procedure Legal_Formal_Attribute is
2190 begin
2191 Check_E0;
2193 if not Is_Entity_Name (P)
2194 or else not Is_Type (Entity (P))
2195 then
2196 Error_Attr_P ("prefix of % attribute must be generic type");
2198 elsif Is_Generic_Actual_Type (Entity (P))
2199 or else In_Instance
2200 or else In_Inlined_Body
2201 then
2202 null;
2204 elsif Is_Generic_Type (Entity (P)) then
2205 if not Is_Indefinite_Subtype (Entity (P)) then
2206 Error_Attr_P
2207 ("prefix of % attribute must be indefinite generic type");
2208 end if;
2210 else
2211 Error_Attr_P
2212 ("prefix of % attribute must be indefinite generic type");
2213 end if;
2215 Set_Etype (N, Standard_Boolean);
2216 end Legal_Formal_Attribute;
2218 ---------------------------------------------------------------
2219 -- Max_Alignment_For_Allocation_Max_Size_In_Storage_Elements --
2220 ---------------------------------------------------------------
2222 procedure Max_Alignment_For_Allocation_Max_Size_In_Storage_Elements is
2223 begin
2224 Check_E0;
2225 Check_Type;
2226 Check_Not_Incomplete_Type;
2227 Set_Etype (N, Universal_Integer);
2228 end Max_Alignment_For_Allocation_Max_Size_In_Storage_Elements;
2230 -------------
2231 -- Min_Max --
2232 -------------
2234 procedure Min_Max is
2235 begin
2236 Check_E2;
2237 Check_Scalar_Type;
2238 Resolve (E1, P_Base_Type);
2239 Resolve (E2, P_Base_Type);
2240 Set_Etype (N, P_Base_Type);
2242 -- Check for comparison on unordered enumeration type
2244 if Bad_Unordered_Enumeration_Reference (N, P_Base_Type) then
2245 Error_Msg_Sloc := Sloc (P_Base_Type);
2246 Error_Msg_NE
2247 ("comparison on unordered enumeration type& declared#?U?",
2248 N, P_Base_Type);
2249 end if;
2250 end Min_Max;
2252 ------------------------
2253 -- Standard_Attribute --
2254 ------------------------
2256 procedure Standard_Attribute (Val : Int) is
2257 begin
2258 Check_Standard_Prefix;
2259 Rewrite (N, Make_Integer_Literal (Loc, Val));
2260 Analyze (N);
2261 Set_Is_Static_Expression (N, True);
2262 end Standard_Attribute;
2264 --------------------
2265 -- Uneval_Old_Msg --
2266 --------------------
2268 procedure Uneval_Old_Msg is
2269 Uneval_Old_Setting : Character;
2270 Prag : Node_Id;
2272 begin
2273 -- If from aspect, then Uneval_Old_Setting comes from flags in the
2274 -- N_Aspect_Specification node that corresponds to the attribute.
2276 -- First find the pragma in which we appear (note that at this stage,
2277 -- even if we appeared originally within an aspect specification, we
2278 -- are now within the corresponding pragma).
2280 Prag := N;
2281 loop
2282 Prag := Parent (Prag);
2283 exit when No (Prag) or else Nkind (Prag) = N_Pragma;
2284 end loop;
2286 if Present (Prag) then
2287 if Uneval_Old_Accept (Prag) then
2288 Uneval_Old_Setting := 'A';
2289 elsif Uneval_Old_Warn (Prag) then
2290 Uneval_Old_Setting := 'W';
2291 else
2292 Uneval_Old_Setting := 'E';
2293 end if;
2295 -- If we did not find the pragma, that's odd, just use the setting
2296 -- from Opt.Uneval_Old. Perhaps this is due to a previous error?
2298 else
2299 Uneval_Old_Setting := Opt.Uneval_Old;
2300 end if;
2302 -- Processing depends on the setting of Uneval_Old
2304 case Uneval_Old_Setting is
2305 when 'E' =>
2306 Error_Attr_P
2307 ("prefix of attribute % that is potentially "
2308 & "unevaluated must denote an entity");
2310 when 'W' =>
2311 Error_Msg_Name_1 := Aname;
2312 Error_Msg_F
2313 ("??prefix of attribute % appears in potentially "
2314 & "unevaluated context, exception may be raised", P);
2316 when 'A' =>
2317 null;
2319 when others =>
2320 raise Program_Error;
2321 end case;
2322 end Uneval_Old_Msg;
2324 -------------------------
2325 -- Unexpected Argument --
2326 -------------------------
2328 procedure Unexpected_Argument (En : Node_Id) is
2329 begin
2330 Error_Attr ("unexpected argument for % attribute", En);
2331 end Unexpected_Argument;
2333 -------------------------------------------------
2334 -- Validate_Non_Static_Attribute_Function_Call --
2335 -------------------------------------------------
2337 -- This function should be moved to Sem_Dist ???
2339 procedure Validate_Non_Static_Attribute_Function_Call is
2340 begin
2341 if In_Preelaborated_Unit
2342 and then not In_Subprogram_Or_Concurrent_Unit
2343 then
2344 Flag_Non_Static_Expr
2345 ("non-static function call in preelaborated unit!", N);
2346 end if;
2347 end Validate_Non_Static_Attribute_Function_Call;
2349 -- Start of processing for Analyze_Attribute
2351 begin
2352 -- Immediate return if unrecognized attribute (already diagnosed
2353 -- by parser, so there is nothing more that we need to do)
2355 if not Is_Attribute_Name (Aname) then
2356 raise Bad_Attribute;
2357 end if;
2359 -- Deal with Ada 83 issues
2361 if Comes_From_Source (N) then
2362 if not Attribute_83 (Attr_Id) then
2363 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
2364 Error_Msg_Name_1 := Aname;
2365 Error_Msg_N ("(Ada 83) attribute% is not standard??", N);
2366 end if;
2368 if Attribute_Impl_Def (Attr_Id) then
2369 Check_Restriction (No_Implementation_Attributes, N);
2370 end if;
2371 end if;
2372 end if;
2374 -- Deal with Ada 2005 attributes that are implementation attributes
2375 -- because they appear in a version of Ada before Ada 2005, and
2376 -- similarly for Ada 2012 attributes appearing in an earlier version.
2378 if (Attribute_05 (Attr_Id) and then Ada_Version < Ada_2005)
2379 or else
2380 (Attribute_12 (Attr_Id) and then Ada_Version < Ada_2012)
2381 then
2382 Check_Restriction (No_Implementation_Attributes, N);
2383 end if;
2385 -- Remote access to subprogram type access attribute reference needs
2386 -- unanalyzed copy for tree transformation. The analyzed copy is used
2387 -- for its semantic information (whether prefix is a remote subprogram
2388 -- name), the unanalyzed copy is used to construct new subtree rooted
2389 -- with N_Aggregate which represents a fat pointer aggregate.
2391 if Aname = Name_Access then
2392 Discard_Node (Copy_Separate_Tree (N));
2393 end if;
2395 -- Analyze prefix and exit if error in analysis. If the prefix is an
2396 -- incomplete type, use full view if available. Note that there are
2397 -- some attributes for which we do not analyze the prefix, since the
2398 -- prefix is not a normal name, or else needs special handling.
2400 if Aname /= Name_Elab_Body and then
2401 Aname /= Name_Elab_Spec and then
2402 Aname /= Name_Elab_Subp_Body and then
2403 Aname /= Name_UET_Address and then
2404 Aname /= Name_Enabled and then
2405 Aname /= Name_Old
2406 then
2407 Analyze (P);
2408 P_Type := Etype (P);
2410 if Is_Entity_Name (P)
2411 and then Present (Entity (P))
2412 and then Is_Type (Entity (P))
2413 then
2414 if Ekind (Entity (P)) = E_Incomplete_Type then
2415 P_Type := Get_Full_View (P_Type);
2416 Set_Entity (P, P_Type);
2417 Set_Etype (P, P_Type);
2419 elsif Entity (P) = Current_Scope
2420 and then Is_Record_Type (Entity (P))
2421 then
2422 -- Use of current instance within the type. Verify that if the
2423 -- attribute appears within a constraint, it yields an access
2424 -- type, other uses are illegal.
2426 declare
2427 Par : Node_Id;
2429 begin
2430 Par := Parent (N);
2431 while Present (Par)
2432 and then Nkind (Parent (Par)) /= N_Component_Definition
2433 loop
2434 Par := Parent (Par);
2435 end loop;
2437 if Present (Par)
2438 and then Nkind (Par) = N_Subtype_Indication
2439 then
2440 if Attr_Id /= Attribute_Access
2441 and then Attr_Id /= Attribute_Unchecked_Access
2442 and then Attr_Id /= Attribute_Unrestricted_Access
2443 then
2444 Error_Msg_N
2445 ("in a constraint the current instance can only"
2446 & " be used with an access attribute", N);
2447 end if;
2448 end if;
2449 end;
2450 end if;
2451 end if;
2453 if P_Type = Any_Type then
2454 raise Bad_Attribute;
2455 end if;
2457 P_Base_Type := Base_Type (P_Type);
2458 end if;
2460 -- Analyze expressions that may be present, exiting if an error occurs
2462 if No (Exprs) then
2463 E1 := Empty;
2464 E2 := Empty;
2466 else
2467 E1 := First (Exprs);
2469 -- Skip analysis for case of Restriction_Set, we do not expect
2470 -- the argument to be analyzed in this case.
2472 if Aname /= Name_Restriction_Set then
2473 Analyze (E1);
2475 -- Check for missing/bad expression (result of previous error)
2477 if No (E1) or else Etype (E1) = Any_Type then
2478 raise Bad_Attribute;
2479 end if;
2480 end if;
2482 E2 := Next (E1);
2484 if Present (E2) then
2485 Analyze (E2);
2487 if Etype (E2) = Any_Type then
2488 raise Bad_Attribute;
2489 end if;
2491 if Present (Next (E2)) then
2492 Unexpected_Argument (Next (E2));
2493 end if;
2494 end if;
2495 end if;
2497 -- Cases where prefix must be resolvable by itself
2499 if Is_Overloaded (P)
2500 and then Aname /= Name_Access
2501 and then Aname /= Name_Address
2502 and then Aname /= Name_Code_Address
2503 and then Aname /= Name_Result
2504 and then Aname /= Name_Unchecked_Access
2505 then
2506 -- The prefix must be resolvable by itself, without reference to the
2507 -- attribute. One case that requires special handling is a prefix
2508 -- that is a function name, where one interpretation may be a
2509 -- parameterless call. Entry attributes are handled specially below.
2511 if Is_Entity_Name (P)
2512 and then not Nam_In (Aname, Name_Count, Name_Caller)
2513 then
2514 Check_Parameterless_Call (P);
2515 end if;
2517 if Is_Overloaded (P) then
2519 -- Ada 2005 (AI-345): Since protected and task types have
2520 -- primitive entry wrappers, the attributes Count, and Caller
2521 -- require a context check
2523 if Nam_In (Aname, Name_Count, Name_Caller) then
2524 declare
2525 Count : Natural := 0;
2526 I : Interp_Index;
2527 It : Interp;
2529 begin
2530 Get_First_Interp (P, I, It);
2531 while Present (It.Nam) loop
2532 if Comes_From_Source (It.Nam) then
2533 Count := Count + 1;
2534 else
2535 Remove_Interp (I);
2536 end if;
2538 Get_Next_Interp (I, It);
2539 end loop;
2541 if Count > 1 then
2542 Error_Attr ("ambiguous prefix for % attribute", P);
2543 else
2544 Set_Is_Overloaded (P, False);
2545 end if;
2546 end;
2548 else
2549 Error_Attr ("ambiguous prefix for % attribute", P);
2550 end if;
2551 end if;
2552 end if;
2554 -- In SPARK, attributes of private types are only allowed if the full
2555 -- type declaration is visible.
2557 -- Note: the check for Present (Entity (P)) defends against some error
2558 -- conditions where the Entity field is not set.
2560 if Is_Entity_Name (P) and then Present (Entity (P))
2561 and then Is_Type (Entity (P))
2562 and then Is_Private_Type (P_Type)
2563 and then not In_Open_Scopes (Scope (P_Type))
2564 and then not In_Spec_Expression
2565 then
2566 Check_SPARK_05_Restriction ("invisible attribute of type", N);
2567 end if;
2569 -- Remaining processing depends on attribute
2571 case Attr_Id is
2573 -- Attributes related to Ada 2012 iterators. Attribute specifications
2574 -- exist for these, but they cannot be queried.
2576 when Attribute_Constant_Indexing |
2577 Attribute_Default_Iterator |
2578 Attribute_Implicit_Dereference |
2579 Attribute_Iterator_Element |
2580 Attribute_Iterable |
2581 Attribute_Variable_Indexing =>
2582 Error_Msg_N ("illegal attribute", N);
2584 -- Internal attributes used to deal with Ada 2012 delayed aspects. These
2585 -- were already rejected by the parser. Thus they shouldn't appear here.
2587 when Internal_Attribute_Id =>
2588 raise Program_Error;
2590 ------------------
2591 -- Abort_Signal --
2592 ------------------
2594 when Attribute_Abort_Signal =>
2595 Check_Standard_Prefix;
2596 Rewrite (N, New_Occurrence_Of (Stand.Abort_Signal, Loc));
2597 Analyze (N);
2599 ------------
2600 -- Access --
2601 ------------
2603 when Attribute_Access =>
2604 Analyze_Access_Attribute;
2606 -------------
2607 -- Address --
2608 -------------
2610 when Attribute_Address =>
2611 Check_E0;
2612 Address_Checks;
2613 Set_Etype (N, RTE (RE_Address));
2615 ------------------
2616 -- Address_Size --
2617 ------------------
2619 when Attribute_Address_Size =>
2620 Standard_Attribute (System_Address_Size);
2622 --------------
2623 -- Adjacent --
2624 --------------
2626 when Attribute_Adjacent =>
2627 Check_Floating_Point_Type_2;
2628 Set_Etype (N, P_Base_Type);
2629 Resolve (E1, P_Base_Type);
2630 Resolve (E2, P_Base_Type);
2632 ---------
2633 -- Aft --
2634 ---------
2636 when Attribute_Aft =>
2637 Check_Fixed_Point_Type_0;
2638 Set_Etype (N, Universal_Integer);
2640 ---------------
2641 -- Alignment --
2642 ---------------
2644 when Attribute_Alignment =>
2646 -- Don't we need more checking here, cf Size ???
2648 Check_E0;
2649 Check_Not_Incomplete_Type;
2650 Check_Not_CPP_Type;
2651 Set_Etype (N, Universal_Integer);
2653 ---------------
2654 -- Asm_Input --
2655 ---------------
2657 when Attribute_Asm_Input =>
2658 Check_Asm_Attribute;
2660 -- The back-end may need to take the address of E2
2662 if Is_Entity_Name (E2) then
2663 Set_Address_Taken (Entity (E2));
2664 end if;
2666 Set_Etype (N, RTE (RE_Asm_Input_Operand));
2668 ----------------
2669 -- Asm_Output --
2670 ----------------
2672 when Attribute_Asm_Output =>
2673 Check_Asm_Attribute;
2675 if Etype (E2) = Any_Type then
2676 return;
2678 elsif Aname = Name_Asm_Output then
2679 if not Is_Variable (E2) then
2680 Error_Attr
2681 ("second argument for Asm_Output is not variable", E2);
2682 end if;
2683 end if;
2685 Note_Possible_Modification (E2, Sure => True);
2687 -- The back-end may need to take the address of E2
2689 if Is_Entity_Name (E2) then
2690 Set_Address_Taken (Entity (E2));
2691 end if;
2693 Set_Etype (N, RTE (RE_Asm_Output_Operand));
2695 -----------------------------
2696 -- Atomic_Always_Lock_Free --
2697 -----------------------------
2699 when Attribute_Atomic_Always_Lock_Free =>
2700 Check_E0;
2701 Check_Type;
2702 Set_Etype (N, Standard_Boolean);
2704 ----------
2705 -- Base --
2706 ----------
2708 -- Note: when the base attribute appears in the context of a subtype
2709 -- mark, the analysis is done by Sem_Ch8.Find_Type, rather than by
2710 -- the following circuit.
2712 when Attribute_Base => Base : declare
2713 Typ : Entity_Id;
2715 begin
2716 Check_E0;
2717 Find_Type (P);
2718 Typ := Entity (P);
2720 if Ada_Version >= Ada_95
2721 and then not Is_Scalar_Type (Typ)
2722 and then not Is_Generic_Type (Typ)
2723 then
2724 Error_Attr_P ("prefix of Base attribute must be scalar type");
2726 elsif Sloc (Typ) = Standard_Location
2727 and then Base_Type (Typ) = Typ
2728 and then Warn_On_Redundant_Constructs
2729 then
2730 Error_Msg_NE -- CODEFIX
2731 ("?r?redundant attribute, & is its own base type", N, Typ);
2732 end if;
2734 if Nkind (Parent (N)) /= N_Attribute_Reference then
2735 Error_Msg_Name_1 := Aname;
2736 Check_SPARK_05_Restriction
2737 ("attribute% is only allowed as prefix of another attribute", P);
2738 end if;
2740 Set_Etype (N, Base_Type (Entity (P)));
2741 Set_Entity (N, Base_Type (Entity (P)));
2742 Rewrite (N, New_Occurrence_Of (Entity (N), Loc));
2743 Analyze (N);
2744 end Base;
2746 ---------
2747 -- Bit --
2748 ---------
2750 when Attribute_Bit => Bit :
2751 begin
2752 Check_E0;
2754 if not Is_Object_Reference (P) then
2755 Error_Attr_P ("prefix for % attribute must be object");
2757 -- What about the access object cases ???
2759 else
2760 null;
2761 end if;
2763 Set_Etype (N, Universal_Integer);
2764 end Bit;
2766 ---------------
2767 -- Bit_Order --
2768 ---------------
2770 when Attribute_Bit_Order => Bit_Order :
2771 begin
2772 Check_E0;
2773 Check_Type;
2775 if not Is_Record_Type (P_Type) then
2776 Error_Attr_P ("prefix of % attribute must be record type");
2777 end if;
2779 if Bytes_Big_Endian xor Reverse_Bit_Order (P_Type) then
2780 Rewrite (N,
2781 New_Occurrence_Of (RTE (RE_High_Order_First), Loc));
2782 else
2783 Rewrite (N,
2784 New_Occurrence_Of (RTE (RE_Low_Order_First), Loc));
2785 end if;
2787 Set_Etype (N, RTE (RE_Bit_Order));
2788 Resolve (N);
2790 -- Reset incorrect indication of staticness
2792 Set_Is_Static_Expression (N, False);
2793 end Bit_Order;
2795 ------------------
2796 -- Bit_Position --
2797 ------------------
2799 -- Note: in generated code, we can have a Bit_Position attribute
2800 -- applied to a (naked) record component (i.e. the prefix is an
2801 -- identifier that references an E_Component or E_Discriminant
2802 -- entity directly, and this is interpreted as expected by Gigi.
2803 -- The following code will not tolerate such usage, but when the
2804 -- expander creates this special case, it marks it as analyzed
2805 -- immediately and sets an appropriate type.
2807 when Attribute_Bit_Position =>
2808 if Comes_From_Source (N) then
2809 Check_Component;
2810 end if;
2812 Set_Etype (N, Universal_Integer);
2814 ------------------
2815 -- Body_Version --
2816 ------------------
2818 when Attribute_Body_Version =>
2819 Check_E0;
2820 Check_Program_Unit;
2821 Set_Etype (N, RTE (RE_Version_String));
2823 --------------
2824 -- Callable --
2825 --------------
2827 when Attribute_Callable =>
2828 Check_E0;
2829 Set_Etype (N, Standard_Boolean);
2830 Check_Task_Prefix;
2832 ------------
2833 -- Caller --
2834 ------------
2836 when Attribute_Caller => Caller : declare
2837 Ent : Entity_Id;
2838 S : Entity_Id;
2840 begin
2841 Check_E0;
2843 if Nkind_In (P, N_Identifier, N_Expanded_Name) then
2844 Ent := Entity (P);
2846 if not Is_Entry (Ent) then
2847 Error_Attr ("invalid entry name", N);
2848 end if;
2850 else
2851 Error_Attr ("invalid entry name", N);
2852 return;
2853 end if;
2855 for J in reverse 0 .. Scope_Stack.Last loop
2856 S := Scope_Stack.Table (J).Entity;
2858 if S = Scope (Ent) then
2859 Error_Attr ("Caller must appear in matching accept or body", N);
2860 elsif S = Ent then
2861 exit;
2862 end if;
2863 end loop;
2865 Set_Etype (N, RTE (RO_AT_Task_Id));
2866 end Caller;
2868 -------------
2869 -- Ceiling --
2870 -------------
2872 when Attribute_Ceiling =>
2873 Check_Floating_Point_Type_1;
2874 Set_Etype (N, P_Base_Type);
2875 Resolve (E1, P_Base_Type);
2877 -----------
2878 -- Class --
2879 -----------
2881 when Attribute_Class =>
2882 Check_Restriction (No_Dispatch, N);
2883 Check_E0;
2884 Find_Type (N);
2886 -- Applying Class to untagged incomplete type is obsolescent in Ada
2887 -- 2005. Note that we can't test Is_Tagged_Type here on P_Type, since
2888 -- this flag gets set by Find_Type in this situation.
2890 if Restriction_Check_Required (No_Obsolescent_Features)
2891 and then Ada_Version >= Ada_2005
2892 and then Ekind (P_Type) = E_Incomplete_Type
2893 then
2894 declare
2895 DN : constant Node_Id := Declaration_Node (P_Type);
2896 begin
2897 if Nkind (DN) = N_Incomplete_Type_Declaration
2898 and then not Tagged_Present (DN)
2899 then
2900 Check_Restriction (No_Obsolescent_Features, P);
2901 end if;
2902 end;
2903 end if;
2905 ------------------
2906 -- Code_Address --
2907 ------------------
2909 when Attribute_Code_Address =>
2910 Check_E0;
2912 if Nkind (P) = N_Attribute_Reference
2913 and then Nam_In (Attribute_Name (P), Name_Elab_Body, Name_Elab_Spec)
2914 then
2915 null;
2917 elsif not Is_Entity_Name (P)
2918 or else (Ekind (Entity (P)) /= E_Function
2919 and then
2920 Ekind (Entity (P)) /= E_Procedure)
2921 then
2922 Error_Attr ("invalid prefix for % attribute", P);
2923 Set_Address_Taken (Entity (P));
2925 -- Issue an error if the prefix denotes an eliminated subprogram
2927 else
2928 Check_For_Eliminated_Subprogram (P, Entity (P));
2929 end if;
2931 Set_Etype (N, RTE (RE_Address));
2933 ----------------------
2934 -- Compiler_Version --
2935 ----------------------
2937 when Attribute_Compiler_Version =>
2938 Check_E0;
2939 Check_Standard_Prefix;
2940 Rewrite (N, Make_String_Literal (Loc, "GNAT " & Gnat_Version_String));
2941 Analyze_And_Resolve (N, Standard_String);
2942 Set_Is_Static_Expression (N, True);
2944 --------------------
2945 -- Component_Size --
2946 --------------------
2948 when Attribute_Component_Size =>
2949 Check_E0;
2950 Set_Etype (N, Universal_Integer);
2952 -- Note: unlike other array attributes, unconstrained arrays are OK
2954 if Is_Array_Type (P_Type) and then not Is_Constrained (P_Type) then
2955 null;
2956 else
2957 Check_Array_Type;
2958 end if;
2960 -------------
2961 -- Compose --
2962 -------------
2964 when Attribute_Compose =>
2965 Check_Floating_Point_Type_2;
2966 Set_Etype (N, P_Base_Type);
2967 Resolve (E1, P_Base_Type);
2968 Resolve (E2, Any_Integer);
2970 -----------------
2971 -- Constrained --
2972 -----------------
2974 when Attribute_Constrained =>
2975 Check_E0;
2976 Set_Etype (N, Standard_Boolean);
2978 -- Case from RM J.4(2) of constrained applied to private type
2980 if Is_Entity_Name (P) and then Is_Type (Entity (P)) then
2981 Check_Restriction (No_Obsolescent_Features, P);
2983 if Warn_On_Obsolescent_Feature then
2984 Error_Msg_N
2985 ("constrained for private type is an " &
2986 "obsolescent feature (RM J.4)?j?", N);
2987 end if;
2989 -- If we are within an instance, the attribute must be legal
2990 -- because it was valid in the generic unit. Ditto if this is
2991 -- an inlining of a function declared in an instance.
2993 if In_Instance or else In_Inlined_Body then
2994 return;
2996 -- For sure OK if we have a real private type itself, but must
2997 -- be completed, cannot apply Constrained to incomplete type.
2999 elsif Is_Private_Type (Entity (P)) then
3001 -- Note: this is one of the Annex J features that does not
3002 -- generate a warning from -gnatwj, since in fact it seems
3003 -- very useful, and is used in the GNAT runtime.
3005 Check_Not_Incomplete_Type;
3006 return;
3007 end if;
3009 -- Normal (non-obsolescent case) of application to object of
3010 -- a discriminated type.
3012 else
3013 Check_Object_Reference (P);
3015 -- If N does not come from source, then we allow the
3016 -- the attribute prefix to be of a private type whose
3017 -- full type has discriminants. This occurs in cases
3018 -- involving expanded calls to stream attributes.
3020 if not Comes_From_Source (N) then
3021 P_Type := Underlying_Type (P_Type);
3022 end if;
3024 -- Must have discriminants or be an access type designating
3025 -- a type with discriminants. If it is a classwide type it
3026 -- has unknown discriminants.
3028 if Has_Discriminants (P_Type)
3029 or else Has_Unknown_Discriminants (P_Type)
3030 or else
3031 (Is_Access_Type (P_Type)
3032 and then Has_Discriminants (Designated_Type (P_Type)))
3033 then
3034 return;
3036 -- The rule given in 3.7.2 is part of static semantics, but the
3037 -- intent is clearly that it be treated as a legality rule, and
3038 -- rechecked in the visible part of an instance. Nevertheless
3039 -- the intent also seems to be it should legally apply to the
3040 -- actual of a formal with unknown discriminants, regardless of
3041 -- whether the actual has discriminants, in which case the value
3042 -- of the attribute is determined using the J.4 rules. This choice
3043 -- seems the most useful, and is compatible with existing tests.
3045 elsif In_Instance then
3046 return;
3048 -- Also allow an object of a generic type if extensions allowed
3049 -- and allow this for any type at all. (this may be obsolete ???)
3051 elsif (Is_Generic_Type (P_Type)
3052 or else Is_Generic_Actual_Type (P_Type))
3053 and then Extensions_Allowed
3054 then
3055 return;
3056 end if;
3057 end if;
3059 -- Fall through if bad prefix
3061 Error_Attr_P
3062 ("prefix of % attribute must be object of discriminated type");
3064 ---------------
3065 -- Copy_Sign --
3066 ---------------
3068 when Attribute_Copy_Sign =>
3069 Check_Floating_Point_Type_2;
3070 Set_Etype (N, P_Base_Type);
3071 Resolve (E1, P_Base_Type);
3072 Resolve (E2, P_Base_Type);
3074 -----------
3075 -- Count --
3076 -----------
3078 when Attribute_Count => Count :
3079 declare
3080 Ent : Entity_Id;
3081 S : Entity_Id;
3082 Tsk : Entity_Id;
3084 begin
3085 Check_E0;
3087 if Nkind_In (P, N_Identifier, N_Expanded_Name) then
3088 Ent := Entity (P);
3090 if Ekind (Ent) /= E_Entry then
3091 Error_Attr ("invalid entry name", N);
3092 end if;
3094 elsif Nkind (P) = N_Indexed_Component then
3095 if not Is_Entity_Name (Prefix (P))
3096 or else No (Entity (Prefix (P)))
3097 or else Ekind (Entity (Prefix (P))) /= E_Entry_Family
3098 then
3099 if Nkind (Prefix (P)) = N_Selected_Component
3100 and then Present (Entity (Selector_Name (Prefix (P))))
3101 and then Ekind (Entity (Selector_Name (Prefix (P)))) =
3102 E_Entry_Family
3103 then
3104 Error_Attr
3105 ("attribute % must apply to entry of current task", P);
3107 else
3108 Error_Attr ("invalid entry family name", P);
3109 end if;
3110 return;
3112 else
3113 Ent := Entity (Prefix (P));
3114 end if;
3116 elsif Nkind (P) = N_Selected_Component
3117 and then Present (Entity (Selector_Name (P)))
3118 and then Ekind (Entity (Selector_Name (P))) = E_Entry
3119 then
3120 Error_Attr
3121 ("attribute % must apply to entry of current task", P);
3123 else
3124 Error_Attr ("invalid entry name", N);
3125 return;
3126 end if;
3128 for J in reverse 0 .. Scope_Stack.Last loop
3129 S := Scope_Stack.Table (J).Entity;
3131 if S = Scope (Ent) then
3132 if Nkind (P) = N_Expanded_Name then
3133 Tsk := Entity (Prefix (P));
3135 -- The prefix denotes either the task type, or else a
3136 -- single task whose task type is being analyzed.
3138 if (Is_Type (Tsk) and then Tsk = S)
3139 or else (not Is_Type (Tsk)
3140 and then Etype (Tsk) = S
3141 and then not (Comes_From_Source (S)))
3142 then
3143 null;
3144 else
3145 Error_Attr
3146 ("Attribute % must apply to entry of current task", N);
3147 end if;
3148 end if;
3150 exit;
3152 elsif Ekind (Scope (Ent)) in Task_Kind
3153 and then
3154 not Ekind_In (S, E_Loop, E_Block, E_Entry, E_Entry_Family)
3155 then
3156 Error_Attr ("Attribute % cannot appear in inner unit", N);
3158 elsif Ekind (Scope (Ent)) = E_Protected_Type
3159 and then not Has_Completion (Scope (Ent))
3160 then
3161 Error_Attr ("attribute % can only be used inside body", N);
3162 end if;
3163 end loop;
3165 if Is_Overloaded (P) then
3166 declare
3167 Index : Interp_Index;
3168 It : Interp;
3170 begin
3171 Get_First_Interp (P, Index, It);
3172 while Present (It.Nam) loop
3173 if It.Nam = Ent then
3174 null;
3176 -- Ada 2005 (AI-345): Do not consider primitive entry
3177 -- wrappers generated for task or protected types.
3179 elsif Ada_Version >= Ada_2005
3180 and then not Comes_From_Source (It.Nam)
3181 then
3182 null;
3184 else
3185 Error_Attr ("ambiguous entry name", N);
3186 end if;
3188 Get_Next_Interp (Index, It);
3189 end loop;
3190 end;
3191 end if;
3193 Set_Etype (N, Universal_Integer);
3194 end Count;
3196 -----------------------
3197 -- Default_Bit_Order --
3198 -----------------------
3200 when Attribute_Default_Bit_Order => Default_Bit_Order : declare
3201 Target_Default_Bit_Order : System.Bit_Order;
3203 begin
3204 Check_Standard_Prefix;
3206 if Bytes_Big_Endian then
3207 Target_Default_Bit_Order := System.High_Order_First;
3208 else
3209 Target_Default_Bit_Order := System.Low_Order_First;
3210 end if;
3212 Rewrite (N,
3213 Make_Integer_Literal (Loc,
3214 UI_From_Int (System.Bit_Order'Pos (Target_Default_Bit_Order))));
3216 Set_Etype (N, Universal_Integer);
3217 Set_Is_Static_Expression (N);
3218 end Default_Bit_Order;
3220 ----------------------------------
3221 -- Default_Scalar_Storage_Order --
3222 ----------------------------------
3224 when Attribute_Default_Scalar_Storage_Order => Default_SSO : declare
3225 RE_Default_SSO : RE_Id;
3227 begin
3228 Check_Standard_Prefix;
3230 case Opt.Default_SSO is
3231 when ' ' =>
3232 if Bytes_Big_Endian then
3233 RE_Default_SSO := RE_High_Order_First;
3234 else
3235 RE_Default_SSO := RE_Low_Order_First;
3236 end if;
3238 when 'H' =>
3239 RE_Default_SSO := RE_High_Order_First;
3241 when 'L' =>
3242 RE_Default_SSO := RE_Low_Order_First;
3244 when others =>
3245 raise Program_Error;
3246 end case;
3248 Rewrite (N, New_Occurrence_Of (RTE (RE_Default_SSO), Loc));
3249 end Default_SSO;
3251 --------------
3252 -- Definite --
3253 --------------
3255 when Attribute_Definite =>
3256 Legal_Formal_Attribute;
3258 -----------
3259 -- Delta --
3260 -----------
3262 when Attribute_Delta =>
3263 Check_Fixed_Point_Type_0;
3264 Set_Etype (N, Universal_Real);
3266 ------------
3267 -- Denorm --
3268 ------------
3270 when Attribute_Denorm =>
3271 Check_Floating_Point_Type_0;
3272 Set_Etype (N, Standard_Boolean);
3274 ---------------------
3275 -- Descriptor_Size --
3276 ---------------------
3278 when Attribute_Descriptor_Size =>
3279 Check_E0;
3281 if not Is_Entity_Name (P) or else not Is_Type (Entity (P)) then
3282 Error_Attr_P ("prefix of attribute % must denote a type");
3283 end if;
3285 Set_Etype (N, Universal_Integer);
3287 ------------
3288 -- Digits --
3289 ------------
3291 when Attribute_Digits =>
3292 Check_E0;
3293 Check_Type;
3295 if not Is_Floating_Point_Type (P_Type)
3296 and then not Is_Decimal_Fixed_Point_Type (P_Type)
3297 then
3298 Error_Attr_P
3299 ("prefix of % attribute must be float or decimal type");
3300 end if;
3302 Set_Etype (N, Universal_Integer);
3304 ---------------
3305 -- Elab_Body --
3306 ---------------
3308 -- Also handles processing for Elab_Spec and Elab_Subp_Body
3310 when Attribute_Elab_Body |
3311 Attribute_Elab_Spec |
3312 Attribute_Elab_Subp_Body =>
3314 Check_E0;
3315 Check_Unit_Name (P);
3316 Set_Etype (N, Standard_Void_Type);
3318 -- We have to manually call the expander in this case to get
3319 -- the necessary expansion (normally attributes that return
3320 -- entities are not expanded).
3322 Expand (N);
3324 ---------------
3325 -- Elab_Spec --
3326 ---------------
3328 -- Shares processing with Elab_Body
3330 ----------------
3331 -- Elaborated --
3332 ----------------
3334 when Attribute_Elaborated =>
3335 Check_E0;
3336 Check_Unit_Name (P);
3337 Set_Etype (N, Standard_Boolean);
3339 ----------
3340 -- Emax --
3341 ----------
3343 when Attribute_Emax =>
3344 Check_Floating_Point_Type_0;
3345 Set_Etype (N, Universal_Integer);
3347 -------------
3348 -- Enabled --
3349 -------------
3351 when Attribute_Enabled =>
3352 Check_Either_E0_Or_E1;
3354 if Present (E1) then
3355 if not Is_Entity_Name (E1) or else No (Entity (E1)) then
3356 Error_Msg_N ("entity name expected for Enabled attribute", E1);
3357 E1 := Empty;
3358 end if;
3359 end if;
3361 if Nkind (P) /= N_Identifier then
3362 Error_Msg_N ("identifier expected (check name)", P);
3363 elsif Get_Check_Id (Chars (P)) = No_Check_Id then
3364 Error_Msg_N ("& is not a recognized check name", P);
3365 end if;
3367 Set_Etype (N, Standard_Boolean);
3369 --------------
3370 -- Enum_Rep --
3371 --------------
3373 when Attribute_Enum_Rep => Enum_Rep : declare
3374 begin
3375 if Present (E1) then
3376 Check_E1;
3377 Check_Discrete_Type;
3378 Resolve (E1, P_Base_Type);
3380 else
3381 if not Is_Entity_Name (P)
3382 or else (not Is_Object (Entity (P))
3383 and then Ekind (Entity (P)) /= E_Enumeration_Literal)
3384 then
3385 Error_Attr_P
3386 ("prefix of % attribute must be " &
3387 "discrete type/object or enum literal");
3388 end if;
3389 end if;
3391 Set_Etype (N, Universal_Integer);
3392 end Enum_Rep;
3394 --------------
3395 -- Enum_Val --
3396 --------------
3398 when Attribute_Enum_Val => Enum_Val : begin
3399 Check_E1;
3400 Check_Type;
3402 if not Is_Enumeration_Type (P_Type) then
3403 Error_Attr_P ("prefix of % attribute must be enumeration type");
3404 end if;
3406 -- If the enumeration type has a standard representation, the effect
3407 -- is the same as 'Val, so rewrite the attribute as a 'Val.
3409 if not Has_Non_Standard_Rep (P_Base_Type) then
3410 Rewrite (N,
3411 Make_Attribute_Reference (Loc,
3412 Prefix => Relocate_Node (Prefix (N)),
3413 Attribute_Name => Name_Val,
3414 Expressions => New_List (Relocate_Node (E1))));
3415 Analyze_And_Resolve (N, P_Base_Type);
3417 -- Non-standard representation case (enumeration with holes)
3419 else
3420 Check_Enum_Image;
3421 Resolve (E1, Any_Integer);
3422 Set_Etype (N, P_Base_Type);
3423 end if;
3424 end Enum_Val;
3426 -------------
3427 -- Epsilon --
3428 -------------
3430 when Attribute_Epsilon =>
3431 Check_Floating_Point_Type_0;
3432 Set_Etype (N, Universal_Real);
3434 --------------
3435 -- Exponent --
3436 --------------
3438 when Attribute_Exponent =>
3439 Check_Floating_Point_Type_1;
3440 Set_Etype (N, Universal_Integer);
3441 Resolve (E1, P_Base_Type);
3443 ------------------
3444 -- External_Tag --
3445 ------------------
3447 when Attribute_External_Tag =>
3448 Check_E0;
3449 Check_Type;
3451 Set_Etype (N, Standard_String);
3453 if not Is_Tagged_Type (P_Type) then
3454 Error_Attr_P ("prefix of % attribute must be tagged");
3455 end if;
3457 ---------------
3458 -- Fast_Math --
3459 ---------------
3461 when Attribute_Fast_Math =>
3462 Check_Standard_Prefix;
3463 Rewrite (N, New_Occurrence_Of (Boolean_Literals (Fast_Math), Loc));
3465 -----------
3466 -- First --
3467 -----------
3469 when Attribute_First =>
3470 Check_Array_Or_Scalar_Type;
3471 Bad_Attribute_For_Predicate;
3473 ---------------
3474 -- First_Bit --
3475 ---------------
3477 when Attribute_First_Bit =>
3478 Check_Component;
3479 Set_Etype (N, Universal_Integer);
3481 -----------------
3482 -- First_Valid --
3483 -----------------
3485 when Attribute_First_Valid =>
3486 Check_First_Last_Valid;
3487 Set_Etype (N, P_Type);
3489 -----------------
3490 -- Fixed_Value --
3491 -----------------
3493 when Attribute_Fixed_Value =>
3494 Check_E1;
3495 Check_Fixed_Point_Type;
3496 Resolve (E1, Any_Integer);
3497 Set_Etype (N, P_Base_Type);
3499 -----------
3500 -- Floor --
3501 -----------
3503 when Attribute_Floor =>
3504 Check_Floating_Point_Type_1;
3505 Set_Etype (N, P_Base_Type);
3506 Resolve (E1, P_Base_Type);
3508 ----------
3509 -- Fore --
3510 ----------
3512 when Attribute_Fore =>
3513 Check_Fixed_Point_Type_0;
3514 Set_Etype (N, Universal_Integer);
3516 --------------
3517 -- Fraction --
3518 --------------
3520 when Attribute_Fraction =>
3521 Check_Floating_Point_Type_1;
3522 Set_Etype (N, P_Base_Type);
3523 Resolve (E1, P_Base_Type);
3525 --------------
3526 -- From_Any --
3527 --------------
3529 when Attribute_From_Any =>
3530 Check_E1;
3531 Check_PolyORB_Attribute;
3532 Set_Etype (N, P_Base_Type);
3534 -----------------------
3535 -- Has_Access_Values --
3536 -----------------------
3538 when Attribute_Has_Access_Values =>
3539 Check_Type;
3540 Check_E0;
3541 Set_Etype (N, Standard_Boolean);
3543 ----------------------
3544 -- Has_Same_Storage --
3545 ----------------------
3547 when Attribute_Has_Same_Storage =>
3548 Check_E1;
3550 -- The arguments must be objects of any type
3552 Analyze_And_Resolve (P);
3553 Analyze_And_Resolve (E1);
3554 Check_Object_Reference (P);
3555 Check_Object_Reference (E1);
3556 Set_Etype (N, Standard_Boolean);
3558 -----------------------
3559 -- Has_Tagged_Values --
3560 -----------------------
3562 when Attribute_Has_Tagged_Values =>
3563 Check_Type;
3564 Check_E0;
3565 Set_Etype (N, Standard_Boolean);
3567 -----------------------
3568 -- Has_Discriminants --
3569 -----------------------
3571 when Attribute_Has_Discriminants =>
3572 Legal_Formal_Attribute;
3574 --------------
3575 -- Identity --
3576 --------------
3578 when Attribute_Identity =>
3579 Check_E0;
3580 Analyze (P);
3582 if Etype (P) = Standard_Exception_Type then
3583 Set_Etype (N, RTE (RE_Exception_Id));
3585 -- Ada 2005 (AI-345): Attribute 'Identity may be applied to task
3586 -- interface class-wide types.
3588 elsif Is_Task_Type (Etype (P))
3589 or else (Is_Access_Type (Etype (P))
3590 and then Is_Task_Type (Designated_Type (Etype (P))))
3591 or else (Ada_Version >= Ada_2005
3592 and then Ekind (Etype (P)) = E_Class_Wide_Type
3593 and then Is_Interface (Etype (P))
3594 and then Is_Task_Interface (Etype (P)))
3595 then
3596 Resolve (P);
3597 Set_Etype (N, RTE (RO_AT_Task_Id));
3599 else
3600 if Ada_Version >= Ada_2005 then
3601 Error_Attr_P
3602 ("prefix of % attribute must be an exception, a " &
3603 "task or a task interface class-wide object");
3604 else
3605 Error_Attr_P
3606 ("prefix of % attribute must be a task or an exception");
3607 end if;
3608 end if;
3610 -----------
3611 -- Image --
3612 -----------
3614 when Attribute_Image => Image :
3615 begin
3616 Check_SPARK_05_Restriction_On_Attribute;
3617 Check_Scalar_Type;
3618 Set_Etype (N, Standard_String);
3620 if Is_Real_Type (P_Type) then
3621 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
3622 Error_Msg_Name_1 := Aname;
3623 Error_Msg_N
3624 ("(Ada 83) % attribute not allowed for real types", N);
3625 end if;
3626 end if;
3628 if Is_Enumeration_Type (P_Type) then
3629 Check_Restriction (No_Enumeration_Maps, N);
3630 end if;
3632 Check_E1;
3633 Resolve (E1, P_Base_Type);
3634 Check_Enum_Image;
3635 Validate_Non_Static_Attribute_Function_Call;
3637 -- Check restriction No_Fixed_IO. Note the check of Comes_From_Source
3638 -- to avoid giving a duplicate message for Img expanded into Image.
3640 if Restriction_Check_Required (No_Fixed_IO)
3641 and then Comes_From_Source (N)
3642 and then Is_Fixed_Point_Type (P_Type)
3643 then
3644 Check_Restriction (No_Fixed_IO, P);
3645 end if;
3646 end Image;
3648 ---------
3649 -- Img --
3650 ---------
3652 when Attribute_Img => Img :
3653 begin
3654 Check_E0;
3655 Set_Etype (N, Standard_String);
3657 if not Is_Scalar_Type (P_Type)
3658 or else (Is_Entity_Name (P) and then Is_Type (Entity (P)))
3659 then
3660 Error_Attr_P
3661 ("prefix of % attribute must be scalar object name");
3662 end if;
3664 Check_Enum_Image;
3666 -- Check restriction No_Fixed_IO
3668 if Restriction_Check_Required (No_Fixed_IO)
3669 and then Is_Fixed_Point_Type (P_Type)
3670 then
3671 Check_Restriction (No_Fixed_IO, P);
3672 end if;
3673 end Img;
3675 -----------
3676 -- Input --
3677 -----------
3679 when Attribute_Input =>
3680 Check_E1;
3681 Check_Stream_Attribute (TSS_Stream_Input);
3682 Set_Etype (N, P_Base_Type);
3684 -------------------
3685 -- Integer_Value --
3686 -------------------
3688 when Attribute_Integer_Value =>
3689 Check_E1;
3690 Check_Integer_Type;
3691 Resolve (E1, Any_Fixed);
3693 -- Signal an error if argument type is not a specific fixed-point
3694 -- subtype. An error has been signalled already if the argument
3695 -- was not of a fixed-point type.
3697 if Etype (E1) = Any_Fixed and then not Error_Posted (E1) then
3698 Error_Attr ("argument of % must be of a fixed-point type", E1);
3699 end if;
3701 Set_Etype (N, P_Base_Type);
3703 -------------------
3704 -- Invalid_Value --
3705 -------------------
3707 when Attribute_Invalid_Value =>
3708 Check_E0;
3709 Check_Scalar_Type;
3710 Set_Etype (N, P_Base_Type);
3711 Invalid_Value_Used := True;
3713 -----------
3714 -- Large --
3715 -----------
3717 when Attribute_Large =>
3718 Check_E0;
3719 Check_Real_Type;
3720 Set_Etype (N, Universal_Real);
3722 ----------
3723 -- Last --
3724 ----------
3726 when Attribute_Last =>
3727 Check_Array_Or_Scalar_Type;
3728 Bad_Attribute_For_Predicate;
3730 --------------
3731 -- Last_Bit --
3732 --------------
3734 when Attribute_Last_Bit =>
3735 Check_Component;
3736 Set_Etype (N, Universal_Integer);
3738 ----------------
3739 -- Last_Valid --
3740 ----------------
3742 when Attribute_Last_Valid =>
3743 Check_First_Last_Valid;
3744 Set_Etype (N, P_Type);
3746 ------------------
3747 -- Leading_Part --
3748 ------------------
3750 when Attribute_Leading_Part =>
3751 Check_Floating_Point_Type_2;
3752 Set_Etype (N, P_Base_Type);
3753 Resolve (E1, P_Base_Type);
3754 Resolve (E2, Any_Integer);
3756 ------------
3757 -- Length --
3758 ------------
3760 when Attribute_Length =>
3761 Check_Array_Type;
3762 Set_Etype (N, Universal_Integer);
3764 -------------------
3765 -- Library_Level --
3766 -------------------
3768 when Attribute_Library_Level =>
3769 Check_E0;
3771 if not Is_Entity_Name (P) then
3772 Error_Attr_P ("prefix of % attribute must be an entity name");
3773 end if;
3775 if not Inside_A_Generic then
3776 Set_Boolean_Result (N,
3777 Is_Library_Level_Entity (Entity (P)));
3778 end if;
3780 Set_Etype (N, Standard_Boolean);
3782 ---------------
3783 -- Lock_Free --
3784 ---------------
3786 when Attribute_Lock_Free =>
3787 Check_E0;
3788 Set_Etype (N, Standard_Boolean);
3790 if not Is_Protected_Type (P_Type) then
3791 Error_Attr_P
3792 ("prefix of % attribute must be a protected object");
3793 end if;
3795 ----------------
3796 -- Loop_Entry --
3797 ----------------
3799 when Attribute_Loop_Entry => Loop_Entry : declare
3800 procedure Check_References_In_Prefix (Loop_Id : Entity_Id);
3801 -- Inspect the prefix for any uses of entities declared within the
3802 -- related loop. Loop_Id denotes the loop identifier.
3804 --------------------------------
3805 -- Check_References_In_Prefix --
3806 --------------------------------
3808 procedure Check_References_In_Prefix (Loop_Id : Entity_Id) is
3809 Loop_Decl : constant Node_Id := Label_Construct (Parent (Loop_Id));
3811 function Check_Reference (Nod : Node_Id) return Traverse_Result;
3812 -- Determine whether a reference mentions an entity declared
3813 -- within the related loop.
3815 function Declared_Within (Nod : Node_Id) return Boolean;
3816 -- Determine whether Nod appears in the subtree of Loop_Decl
3818 ---------------------
3819 -- Check_Reference --
3820 ---------------------
3822 function Check_Reference (Nod : Node_Id) return Traverse_Result is
3823 begin
3824 if Nkind (Nod) = N_Identifier
3825 and then Present (Entity (Nod))
3826 and then Declared_Within (Declaration_Node (Entity (Nod)))
3827 then
3828 Error_Attr
3829 ("prefix of attribute % cannot reference local entities",
3830 Nod);
3831 return Abandon;
3832 else
3833 return OK;
3834 end if;
3835 end Check_Reference;
3837 procedure Check_References is new Traverse_Proc (Check_Reference);
3839 ---------------------
3840 -- Declared_Within --
3841 ---------------------
3843 function Declared_Within (Nod : Node_Id) return Boolean is
3844 Stmt : Node_Id;
3846 begin
3847 Stmt := Nod;
3848 while Present (Stmt) loop
3849 if Stmt = Loop_Decl then
3850 return True;
3852 -- Prevent the search from going too far
3854 elsif Is_Body_Or_Package_Declaration (Stmt) then
3855 exit;
3856 end if;
3858 Stmt := Parent (Stmt);
3859 end loop;
3861 return False;
3862 end Declared_Within;
3864 -- Start of processing for Check_Prefix_For_Local_References
3866 begin
3867 Check_References (P);
3868 end Check_References_In_Prefix;
3870 -- Local variables
3872 Context : constant Node_Id := Parent (N);
3873 Attr : Node_Id;
3874 Enclosing_Loop : Node_Id;
3875 Loop_Id : Entity_Id := Empty;
3876 Scop : Entity_Id;
3877 Stmt : Node_Id;
3878 Enclosing_Pragma : Node_Id := Empty;
3880 -- Start of processing for Loop_Entry
3882 begin
3883 Attr := N;
3885 -- Set the type of the attribute now to ensure the successfull
3886 -- continuation of analysis even if the attribute is misplaced.
3888 Set_Etype (Attr, P_Type);
3890 -- Attribute 'Loop_Entry may appear in several flavors:
3892 -- * Prefix'Loop_Entry - in this form, the attribute applies to the
3893 -- nearest enclosing loop.
3895 -- * Prefix'Loop_Entry (Expr) - depending on what Expr denotes, the
3896 -- attribute may be related to a loop denoted by label Expr or
3897 -- the prefix may denote an array object and Expr may act as an
3898 -- indexed component.
3900 -- * Prefix'Loop_Entry (Expr1, ..., ExprN) - the attribute applies
3901 -- to the nearest enclosing loop, all expressions are part of
3902 -- an indexed component.
3904 -- * Prefix'Loop_Entry (Expr) (...) (...) - depending on what Expr
3905 -- denotes, the attribute may be related to a loop denoted by
3906 -- label Expr or the prefix may denote a multidimensional array
3907 -- array object and Expr along with the rest of the expressions
3908 -- may act as indexed components.
3910 -- Regardless of variations, the attribute reference does not have an
3911 -- expression list. Instead, all available expressions are stored as
3912 -- indexed components.
3914 -- When the attribute is part of an indexed component, find the first
3915 -- expression as it will determine the semantics of 'Loop_Entry.
3917 if Nkind (Context) = N_Indexed_Component then
3918 E1 := First (Expressions (Context));
3919 E2 := Next (E1);
3921 -- The attribute reference appears in the following form:
3923 -- Prefix'Loop_Entry (Exp1, Expr2, ..., ExprN) [(...)]
3925 -- In this case, the loop name is omitted and no rewriting is
3926 -- required.
3928 if Present (E2) then
3929 null;
3931 -- The form of the attribute is:
3933 -- Prefix'Loop_Entry (Expr) [(...)]
3935 -- If Expr denotes a loop entry, the whole attribute and indexed
3936 -- component will have to be rewritten to reflect this relation.
3938 else
3939 pragma Assert (Present (E1));
3941 -- Do not expand the expression as it may have side effects.
3942 -- Simply preanalyze to determine whether it is a loop name or
3943 -- something else.
3945 Preanalyze_And_Resolve (E1);
3947 if Is_Entity_Name (E1)
3948 and then Present (Entity (E1))
3949 and then Ekind (Entity (E1)) = E_Loop
3950 then
3951 Loop_Id := Entity (E1);
3953 -- Transform the attribute and enclosing indexed component
3955 Set_Expressions (N, Expressions (Context));
3956 Rewrite (Context, N);
3957 Set_Etype (Context, P_Type);
3959 Attr := Context;
3960 end if;
3961 end if;
3962 end if;
3964 -- The prefix must denote an object
3966 if not Is_Object_Reference (P) then
3967 Error_Attr_P ("prefix of attribute % must denote an object");
3968 end if;
3970 -- The prefix cannot be of a limited type because the expansion of
3971 -- Loop_Entry must create a constant initialized by the evaluated
3972 -- prefix.
3974 if Is_Limited_View (Etype (P)) then
3975 Error_Attr_P ("prefix of attribute % cannot be limited");
3976 end if;
3978 -- Climb the parent chain to verify the location of the attribute and
3979 -- find the enclosing loop.
3981 Stmt := Attr;
3982 while Present (Stmt) loop
3984 -- Locate the corresponding enclosing pragma. Note that in the
3985 -- case of Assert[And_Cut] and Assume, we have already checked
3986 -- that the pragma appears in an appropriate loop location.
3988 if Nkind (Original_Node (Stmt)) = N_Pragma
3989 and then Nam_In (Pragma_Name (Original_Node (Stmt)),
3990 Name_Loop_Invariant,
3991 Name_Loop_Variant,
3992 Name_Assert,
3993 Name_Assert_And_Cut,
3994 Name_Assume)
3995 then
3996 Enclosing_Pragma := Original_Node (Stmt);
3998 -- Locate the enclosing loop (if any). Note that Ada 2012 array
3999 -- iteration may be expanded into several nested loops, we are
4000 -- interested in the outermost one which has the loop identifier.
4002 elsif Nkind (Stmt) = N_Loop_Statement
4003 and then Present (Identifier (Stmt))
4004 then
4005 Enclosing_Loop := Stmt;
4007 -- The original attribute reference may lack a loop name. Use
4008 -- the name of the enclosing loop because it is the related
4009 -- loop.
4011 if No (Loop_Id) then
4012 Loop_Id := Entity (Identifier (Enclosing_Loop));
4013 end if;
4015 exit;
4017 -- Prevent the search from going too far
4019 elsif Is_Body_Or_Package_Declaration (Stmt) then
4020 exit;
4021 end if;
4023 Stmt := Parent (Stmt);
4024 end loop;
4026 -- Loop_Entry must appear within a Loop_Assertion pragma (Assert,
4027 -- Assert_And_Cut, Assume count as loop assertion pragmas for this
4028 -- purpose if they appear in an appropriate location in a loop,
4029 -- which was already checked by the top level pragma circuit).
4031 if No (Enclosing_Pragma) then
4032 Error_Attr ("attribute% must appear within appropriate pragma", N);
4033 end if;
4035 -- A Loop_Entry that applies to a given loop statement must not
4036 -- appear within a body of accept statement, if this construct is
4037 -- itself enclosed by the given loop statement.
4039 for Index in reverse 0 .. Scope_Stack.Last loop
4040 Scop := Scope_Stack.Table (Index).Entity;
4042 if Ekind (Scop) = E_Loop and then Scop = Loop_Id then
4043 exit;
4044 elsif Ekind_In (Scop, E_Block, E_Loop, E_Return_Statement) then
4045 null;
4046 else
4047 Error_Attr
4048 ("attribute % cannot appear in body or accept statement", N);
4049 exit;
4050 end if;
4051 end loop;
4053 -- The prefix cannot mention entities declared within the related
4054 -- loop because they will not be visible once the prefix is moved
4055 -- outside the loop.
4057 Check_References_In_Prefix (Loop_Id);
4059 -- The prefix must denote a static entity if the pragma does not
4060 -- apply to the innermost enclosing loop statement, or if it appears
4061 -- within a potentially unevaluated epxression.
4063 if Is_Entity_Name (P)
4064 or else Nkind (Parent (P)) = N_Object_Renaming_Declaration
4065 then
4066 null;
4068 elsif Present (Enclosing_Loop)
4069 and then Entity (Identifier (Enclosing_Loop)) /= Loop_Id
4070 then
4071 Error_Attr_P
4072 ("prefix of attribute % that applies to outer loop must denote "
4073 & "an entity");
4075 elsif Is_Potentially_Unevaluated (P) then
4076 Uneval_Old_Msg;
4077 end if;
4079 -- Replace the Loop_Entry attribute reference by its prefix if the
4080 -- related pragma is ignored. This transformation is OK with respect
4081 -- to typing because Loop_Entry's type is that of its prefix. This
4082 -- early transformation also avoids the generation of a useless loop
4083 -- entry constant.
4085 if Is_Ignored (Enclosing_Pragma) then
4086 Rewrite (N, Relocate_Node (P));
4087 end if;
4089 Preanalyze_And_Resolve (P);
4090 end Loop_Entry;
4092 -------------
4093 -- Machine --
4094 -------------
4096 when Attribute_Machine =>
4097 Check_Floating_Point_Type_1;
4098 Set_Etype (N, P_Base_Type);
4099 Resolve (E1, P_Base_Type);
4101 ------------------
4102 -- Machine_Emax --
4103 ------------------
4105 when Attribute_Machine_Emax =>
4106 Check_Floating_Point_Type_0;
4107 Set_Etype (N, Universal_Integer);
4109 ------------------
4110 -- Machine_Emin --
4111 ------------------
4113 when Attribute_Machine_Emin =>
4114 Check_Floating_Point_Type_0;
4115 Set_Etype (N, Universal_Integer);
4117 ----------------------
4118 -- Machine_Mantissa --
4119 ----------------------
4121 when Attribute_Machine_Mantissa =>
4122 Check_Floating_Point_Type_0;
4123 Set_Etype (N, Universal_Integer);
4125 -----------------------
4126 -- Machine_Overflows --
4127 -----------------------
4129 when Attribute_Machine_Overflows =>
4130 Check_Real_Type;
4131 Check_E0;
4132 Set_Etype (N, Standard_Boolean);
4134 -------------------
4135 -- Machine_Radix --
4136 -------------------
4138 when Attribute_Machine_Radix =>
4139 Check_Real_Type;
4140 Check_E0;
4141 Set_Etype (N, Universal_Integer);
4143 ----------------------
4144 -- Machine_Rounding --
4145 ----------------------
4147 when Attribute_Machine_Rounding =>
4148 Check_Floating_Point_Type_1;
4149 Set_Etype (N, P_Base_Type);
4150 Resolve (E1, P_Base_Type);
4152 --------------------
4153 -- Machine_Rounds --
4154 --------------------
4156 when Attribute_Machine_Rounds =>
4157 Check_Real_Type;
4158 Check_E0;
4159 Set_Etype (N, Standard_Boolean);
4161 ------------------
4162 -- Machine_Size --
4163 ------------------
4165 when Attribute_Machine_Size =>
4166 Check_E0;
4167 Check_Type;
4168 Check_Not_Incomplete_Type;
4169 Set_Etype (N, Universal_Integer);
4171 --------------
4172 -- Mantissa --
4173 --------------
4175 when Attribute_Mantissa =>
4176 Check_E0;
4177 Check_Real_Type;
4178 Set_Etype (N, Universal_Integer);
4180 ---------
4181 -- Max --
4182 ---------
4184 when Attribute_Max =>
4185 Min_Max;
4187 ----------------------------------
4188 -- Max_Alignment_For_Allocation --
4189 ----------------------------------
4191 when Attribute_Max_Size_In_Storage_Elements =>
4192 Max_Alignment_For_Allocation_Max_Size_In_Storage_Elements;
4194 ----------------------------------
4195 -- Max_Size_In_Storage_Elements --
4196 ----------------------------------
4198 when Attribute_Max_Alignment_For_Allocation =>
4199 Max_Alignment_For_Allocation_Max_Size_In_Storage_Elements;
4201 -----------------------
4202 -- Maximum_Alignment --
4203 -----------------------
4205 when Attribute_Maximum_Alignment =>
4206 Standard_Attribute (Ttypes.Maximum_Alignment);
4208 --------------------
4209 -- Mechanism_Code --
4210 --------------------
4212 when Attribute_Mechanism_Code =>
4213 if not Is_Entity_Name (P)
4214 or else not Is_Subprogram (Entity (P))
4215 then
4216 Error_Attr_P ("prefix of % attribute must be subprogram");
4217 end if;
4219 Check_Either_E0_Or_E1;
4221 if Present (E1) then
4222 Resolve (E1, Any_Integer);
4223 Set_Etype (E1, Standard_Integer);
4225 if not Is_OK_Static_Expression (E1) then
4226 Flag_Non_Static_Expr
4227 ("expression for parameter number must be static!", E1);
4228 Error_Attr;
4230 elsif UI_To_Int (Intval (E1)) > Number_Formals (Entity (P))
4231 or else UI_To_Int (Intval (E1)) < 0
4232 then
4233 Error_Attr ("invalid parameter number for % attribute", E1);
4234 end if;
4235 end if;
4237 Set_Etype (N, Universal_Integer);
4239 ---------
4240 -- Min --
4241 ---------
4243 when Attribute_Min =>
4244 Min_Max;
4246 ---------
4247 -- Mod --
4248 ---------
4250 when Attribute_Mod =>
4252 -- Note: this attribute is only allowed in Ada 2005 mode, but
4253 -- we do not need to test that here, since Mod is only recognized
4254 -- as an attribute name in Ada 2005 mode during the parse.
4256 Check_E1;
4257 Check_Modular_Integer_Type;
4258 Resolve (E1, Any_Integer);
4259 Set_Etype (N, P_Base_Type);
4261 -----------
4262 -- Model --
4263 -----------
4265 when Attribute_Model =>
4266 Check_Floating_Point_Type_1;
4267 Set_Etype (N, P_Base_Type);
4268 Resolve (E1, P_Base_Type);
4270 ----------------
4271 -- Model_Emin --
4272 ----------------
4274 when Attribute_Model_Emin =>
4275 Check_Floating_Point_Type_0;
4276 Set_Etype (N, Universal_Integer);
4278 -------------------
4279 -- Model_Epsilon --
4280 -------------------
4282 when Attribute_Model_Epsilon =>
4283 Check_Floating_Point_Type_0;
4284 Set_Etype (N, Universal_Real);
4286 --------------------
4287 -- Model_Mantissa --
4288 --------------------
4290 when Attribute_Model_Mantissa =>
4291 Check_Floating_Point_Type_0;
4292 Set_Etype (N, Universal_Integer);
4294 -----------------
4295 -- Model_Small --
4296 -----------------
4298 when Attribute_Model_Small =>
4299 Check_Floating_Point_Type_0;
4300 Set_Etype (N, Universal_Real);
4302 -------------
4303 -- Modulus --
4304 -------------
4306 when Attribute_Modulus =>
4307 Check_E0;
4308 Check_Modular_Integer_Type;
4309 Set_Etype (N, Universal_Integer);
4311 --------------------
4312 -- Null_Parameter --
4313 --------------------
4315 when Attribute_Null_Parameter => Null_Parameter : declare
4316 Parnt : constant Node_Id := Parent (N);
4317 GParnt : constant Node_Id := Parent (Parnt);
4319 procedure Bad_Null_Parameter (Msg : String);
4320 -- Used if bad Null parameter attribute node is found. Issues
4321 -- given error message, and also sets the type to Any_Type to
4322 -- avoid blowups later on from dealing with a junk node.
4324 procedure Must_Be_Imported (Proc_Ent : Entity_Id);
4325 -- Called to check that Proc_Ent is imported subprogram
4327 ------------------------
4328 -- Bad_Null_Parameter --
4329 ------------------------
4331 procedure Bad_Null_Parameter (Msg : String) is
4332 begin
4333 Error_Msg_N (Msg, N);
4334 Set_Etype (N, Any_Type);
4335 end Bad_Null_Parameter;
4337 ----------------------
4338 -- Must_Be_Imported --
4339 ----------------------
4341 procedure Must_Be_Imported (Proc_Ent : Entity_Id) is
4342 Pent : constant Entity_Id := Ultimate_Alias (Proc_Ent);
4344 begin
4345 -- Ignore check if procedure not frozen yet (we will get
4346 -- another chance when the default parameter is reanalyzed)
4348 if not Is_Frozen (Pent) then
4349 return;
4351 elsif not Is_Imported (Pent) then
4352 Bad_Null_Parameter
4353 ("Null_Parameter can only be used with imported subprogram");
4355 else
4356 return;
4357 end if;
4358 end Must_Be_Imported;
4360 -- Start of processing for Null_Parameter
4362 begin
4363 Check_Type;
4364 Check_E0;
4365 Set_Etype (N, P_Type);
4367 -- Case of attribute used as default expression
4369 if Nkind (Parnt) = N_Parameter_Specification then
4370 Must_Be_Imported (Defining_Entity (GParnt));
4372 -- Case of attribute used as actual for subprogram (positional)
4374 elsif Nkind (Parnt) in N_Subprogram_Call
4375 and then Is_Entity_Name (Name (Parnt))
4376 then
4377 Must_Be_Imported (Entity (Name (Parnt)));
4379 -- Case of attribute used as actual for subprogram (named)
4381 elsif Nkind (Parnt) = N_Parameter_Association
4382 and then Nkind (GParnt) in N_Subprogram_Call
4383 and then Is_Entity_Name (Name (GParnt))
4384 then
4385 Must_Be_Imported (Entity (Name (GParnt)));
4387 -- Not an allowed case
4389 else
4390 Bad_Null_Parameter
4391 ("Null_Parameter must be actual or default parameter");
4392 end if;
4393 end Null_Parameter;
4395 -----------------
4396 -- Object_Size --
4397 -----------------
4399 when Attribute_Object_Size =>
4400 Check_E0;
4401 Check_Type;
4402 Check_Not_Incomplete_Type;
4403 Set_Etype (N, Universal_Integer);
4405 ---------
4406 -- Old --
4407 ---------
4409 when Attribute_Old => Old : declare
4410 procedure Check_References_In_Prefix (Subp_Id : Entity_Id);
4411 -- Inspect the contents of the prefix and detect illegal uses of a
4412 -- nested 'Old, attribute 'Result or a use of an entity declared in
4413 -- the related postcondition expression. Subp_Id is the subprogram to
4414 -- which the related postcondition applies.
4416 procedure Check_Use_In_Contract_Cases (Prag : Node_Id);
4417 -- Perform various semantic checks related to the placement of the
4418 -- attribute in pragma Contract_Cases.
4420 procedure Check_Use_In_Test_Case (Prag : Node_Id);
4421 -- Perform various semantic checks related to the placement of the
4422 -- attribute in pragma Contract_Cases.
4424 --------------------------------
4425 -- Check_References_In_Prefix --
4426 --------------------------------
4428 procedure Check_References_In_Prefix (Subp_Id : Entity_Id) is
4429 function Check_Reference (Nod : Node_Id) return Traverse_Result;
4430 -- Detect attribute 'Old, attribute 'Result of a use of an entity
4431 -- and perform the appropriate semantic check.
4433 ---------------------
4434 -- Check_Reference --
4435 ---------------------
4437 function Check_Reference (Nod : Node_Id) return Traverse_Result is
4438 begin
4439 -- Attributes 'Old and 'Result cannot appear in the prefix of
4440 -- another attribute 'Old.
4442 if Nkind (Nod) = N_Attribute_Reference
4443 and then Nam_In (Attribute_Name (Nod), Name_Old,
4444 Name_Result)
4445 then
4446 Error_Msg_Name_1 := Attribute_Name (Nod);
4447 Error_Msg_Name_2 := Name_Old;
4448 Error_Msg_N
4449 ("attribute % cannot appear in the prefix of attribute %",
4450 Nod);
4451 return Abandon;
4453 -- Entities mentioned within the prefix of attribute 'Old must
4454 -- be global to the related postcondition. If this is not the
4455 -- case, then the scope of the local entity is nested within
4456 -- that of the subprogram.
4458 elsif Nkind (Nod) = N_Identifier
4459 and then Present (Entity (Nod))
4460 and then Scope_Within (Scope (Entity (Nod)), Subp_Id)
4461 then
4462 Error_Attr
4463 ("prefix of attribute % cannot reference local entities",
4464 Nod);
4465 return Abandon;
4466 else
4467 return OK;
4468 end if;
4469 end Check_Reference;
4471 procedure Check_References is new Traverse_Proc (Check_Reference);
4473 -- Start of processing for Check_References_In_Prefix
4475 begin
4476 Check_References (P);
4477 end Check_References_In_Prefix;
4479 ---------------------------------
4480 -- Check_Use_In_Contract_Cases --
4481 ---------------------------------
4483 procedure Check_Use_In_Contract_Cases (Prag : Node_Id) is
4484 Cases : constant Node_Id :=
4485 Get_Pragma_Arg
4486 (First (Pragma_Argument_Associations (Prag)));
4487 Expr : Node_Id;
4489 begin
4490 -- Climb the parent chain to reach the top of the expression where
4491 -- attribute 'Old resides.
4493 Expr := N;
4494 while Parent (Parent (Expr)) /= Cases loop
4495 Expr := Parent (Expr);
4496 end loop;
4498 -- Ensure that the obtained expression is the consequence of a
4499 -- contract case as this is the only postcondition-like part of
4500 -- the pragma. Otherwise, attribute 'Old appears in the condition
4501 -- of a contract case. Emit an error since this is not a
4502 -- postcondition-like context. (SPARK RM 6.1.3(2))
4504 if Expr /= Expression (Parent (Expr)) then
4505 Error_Attr
4506 ("attribute % cannot appear in the condition "
4507 & "of a contract case", P);
4508 end if;
4509 end Check_Use_In_Contract_Cases;
4511 ----------------------------
4512 -- Check_Use_In_Test_Case --
4513 ----------------------------
4515 procedure Check_Use_In_Test_Case (Prag : Node_Id) is
4516 Ensures : constant Node_Id := Get_Ensures_From_CTC_Pragma (Prag);
4517 Expr : Node_Id;
4519 begin
4520 -- Climb the parent chain to reach the top of the Ensures part of
4521 -- pragma Test_Case.
4523 Expr := N;
4524 while Expr /= Prag loop
4525 if Expr = Ensures then
4526 return;
4527 end if;
4529 Expr := Parent (Expr);
4530 end loop;
4532 -- If we get there, then attribute 'Old appears in the requires
4533 -- expression of pragma Test_Case which is not a postcondition-
4534 -- like context.
4536 Error_Attr
4537 ("attribute % cannot appear in the requires expression of a "
4538 & "test case", P);
4539 end Check_Use_In_Test_Case;
4541 -- Local variables
4543 CS : Entity_Id;
4544 -- The enclosing scope, excluding loops for quantified expressions.
4545 -- During analysis, it is the postcondition subprogram. During
4546 -- pre-analysis, it is the scope of the subprogram declaration.
4548 Prag : Node_Id;
4549 -- During pre-analysis, Prag is the enclosing pragma node if any
4551 -- Start of processing for Old
4553 begin
4554 Prag := Empty;
4556 -- Find enclosing scopes, excluding loops
4558 CS := Current_Scope;
4559 while Ekind (CS) = E_Loop loop
4560 CS := Scope (CS);
4561 end loop;
4563 -- A Contract_Cases, Postcondition or Test_Case pragma is in the
4564 -- process of being preanalyzed. Perform the semantic checks now
4565 -- before the pragma is relocated and/or expanded.
4567 -- For a generic subprogram, postconditions are preanalyzed as well
4568 -- for name capture, and still appear within an aspect spec.
4570 if In_Spec_Expression or Inside_A_Generic then
4571 Prag := N;
4572 while Present (Prag)
4573 and then not Nkind_In (Prag, N_Aspect_Specification,
4574 N_Function_Specification,
4575 N_Pragma,
4576 N_Procedure_Specification,
4577 N_Subprogram_Body)
4578 loop
4579 Prag := Parent (Prag);
4580 end loop;
4582 -- In ASIS mode, the aspect itself is analyzed, in addition to the
4583 -- corresponding pragma. Don't issue errors when analyzing aspect.
4585 if Nkind (Prag) = N_Aspect_Specification
4586 and then Chars (Identifier (Prag)) = Name_Post
4587 then
4588 null;
4590 -- In all other cases the related context must be a pragma
4592 elsif Nkind (Prag) /= N_Pragma then
4593 Error_Attr ("% attribute can only appear in postcondition", P);
4595 -- Verify the placement of the attribute with respect to the
4596 -- related pragma.
4598 else
4599 case Get_Pragma_Id (Prag) is
4600 when Pragma_Contract_Cases =>
4601 Check_Use_In_Contract_Cases (Prag);
4603 when Pragma_Postcondition | Pragma_Refined_Post =>
4604 null;
4606 when Pragma_Test_Case =>
4607 Check_Use_In_Test_Case (Prag);
4609 when others =>
4610 Error_Attr
4611 ("% attribute can only appear in postcondition", P);
4612 end case;
4613 end if;
4615 -- Check the legality of attribute 'Old when it appears inside pragma
4616 -- Refined_Post. These specialized checks are required only when code
4617 -- generation is disabled. In the general case pragma Refined_Post is
4618 -- transformed into pragma Check by Process_PPCs which in turn is
4619 -- relocated to procedure _Postconditions. From then on the legality
4620 -- of 'Old is determined as usual.
4622 elsif not Expander_Active and then In_Refined_Post then
4623 Preanalyze_And_Resolve (P);
4624 Check_References_In_Prefix (CS);
4625 P_Type := Etype (P);
4626 Set_Etype (N, P_Type);
4628 if Is_Limited_Type (P_Type) then
4629 Error_Attr ("attribute % cannot apply to limited objects", P);
4630 end if;
4632 if Is_Entity_Name (P)
4633 and then Is_Constant_Object (Entity (P))
4634 then
4635 Error_Msg_N
4636 ("??attribute Old applied to constant has no effect", P);
4637 end if;
4639 return;
4641 -- Body case, where we must be inside a generated _Postconditions
4642 -- procedure, or else the attribute use is definitely misplaced. The
4643 -- postcondition itself may have generated transient scopes, and is
4644 -- not necessarily the current one.
4646 else
4647 while Present (CS) and then CS /= Standard_Standard loop
4648 if Chars (CS) = Name_uPostconditions then
4649 exit;
4650 else
4651 CS := Scope (CS);
4652 end if;
4653 end loop;
4655 if Chars (CS) /= Name_uPostconditions then
4656 Error_Attr ("% attribute can only appear in postcondition", P);
4657 end if;
4658 end if;
4660 -- If the attribute reference is generated for a Requires clause,
4661 -- then no expressions follow. Otherwise it is a primary, in which
4662 -- case, if expressions follow, the attribute reference must be an
4663 -- indexable object, so rewrite the node accordingly.
4665 if Present (E1) then
4666 Rewrite (N,
4667 Make_Indexed_Component (Loc,
4668 Prefix =>
4669 Make_Attribute_Reference (Loc,
4670 Prefix => Relocate_Node (Prefix (N)),
4671 Attribute_Name => Name_Old),
4672 Expressions => Expressions (N)));
4674 Analyze (N);
4675 return;
4676 end if;
4678 Check_E0;
4680 -- Prefix has not been analyzed yet, and its full analysis will take
4681 -- place during expansion (see below).
4683 Preanalyze_And_Resolve (P);
4684 Check_References_In_Prefix (CS);
4685 P_Type := Etype (P);
4686 Set_Etype (N, P_Type);
4688 if Is_Limited_Type (P_Type) then
4689 Error_Attr ("attribute % cannot apply to limited objects", P);
4690 end if;
4692 if Is_Entity_Name (P)
4693 and then Is_Constant_Object (Entity (P))
4694 then
4695 Error_Msg_N
4696 ("??attribute Old applied to constant has no effect", P);
4697 end if;
4699 -- Check that the prefix of 'Old is an entity when it may be
4700 -- potentially unevaluated (6.1.1 (27/3)).
4702 if Present (Prag)
4703 and then Is_Potentially_Unevaluated (N)
4704 and then not Is_Entity_Name (P)
4705 then
4706 Uneval_Old_Msg;
4707 end if;
4709 -- The attribute appears within a pre/postcondition, but refers to
4710 -- an entity in the enclosing subprogram. If it is a component of
4711 -- a formal its expansion might generate actual subtypes that may
4712 -- be referenced in an inner context, and which must be elaborated
4713 -- within the subprogram itself. If the prefix includes a function
4714 -- call it may involve finalization actions that should only be
4715 -- inserted when the attribute has been rewritten as a declarations.
4716 -- As a result, if the prefix is not a simple name we create
4717 -- a declaration for it now, and insert it at the start of the
4718 -- enclosing subprogram. This is properly an expansion activity
4719 -- but it has to be performed now to prevent out-of-order issues.
4721 -- This expansion is both harmful and not needed in SPARK mode, since
4722 -- the formal verification backend relies on the types of nodes
4723 -- (hence is not robust w.r.t. a change to base type here), and does
4724 -- not suffer from the out-of-order issue described above. Thus, this
4725 -- expansion is skipped in SPARK mode.
4727 if not Is_Entity_Name (P) and then not GNATprove_Mode then
4728 P_Type := Base_Type (P_Type);
4729 Set_Etype (N, P_Type);
4730 Set_Etype (P, P_Type);
4731 Analyze_Dimension (N);
4732 Expand (N);
4733 end if;
4734 end Old;
4736 ----------------------
4737 -- Overlaps_Storage --
4738 ----------------------
4740 when Attribute_Overlaps_Storage =>
4741 Check_E1;
4743 -- Both arguments must be objects of any type
4745 Analyze_And_Resolve (P);
4746 Analyze_And_Resolve (E1);
4747 Check_Object_Reference (P);
4748 Check_Object_Reference (E1);
4749 Set_Etype (N, Standard_Boolean);
4751 ------------
4752 -- Output --
4753 ------------
4755 when Attribute_Output =>
4756 Check_E2;
4757 Check_Stream_Attribute (TSS_Stream_Output);
4758 Set_Etype (N, Standard_Void_Type);
4759 Resolve (N, Standard_Void_Type);
4761 ------------------
4762 -- Partition_ID --
4763 ------------------
4765 when Attribute_Partition_ID => Partition_Id :
4766 begin
4767 Check_E0;
4769 if P_Type /= Any_Type then
4770 if not Is_Library_Level_Entity (Entity (P)) then
4771 Error_Attr_P
4772 ("prefix of % attribute must be library-level entity");
4774 -- The defining entity of prefix should not be declared inside a
4775 -- Pure unit. RM E.1(8). Is_Pure was set during declaration.
4777 elsif Is_Entity_Name (P)
4778 and then Is_Pure (Entity (P))
4779 then
4780 Error_Attr_P ("prefix of% attribute must not be declared pure");
4781 end if;
4782 end if;
4784 Set_Etype (N, Universal_Integer);
4785 end Partition_Id;
4787 -------------------------
4788 -- Passed_By_Reference --
4789 -------------------------
4791 when Attribute_Passed_By_Reference =>
4792 Check_E0;
4793 Check_Type;
4794 Set_Etype (N, Standard_Boolean);
4796 ------------------
4797 -- Pool_Address --
4798 ------------------
4800 when Attribute_Pool_Address =>
4801 Check_E0;
4802 Set_Etype (N, RTE (RE_Address));
4804 ---------
4805 -- Pos --
4806 ---------
4808 when Attribute_Pos =>
4809 Check_Discrete_Type;
4810 Check_E1;
4812 if Is_Boolean_Type (P_Type) then
4813 Error_Msg_Name_1 := Aname;
4814 Error_Msg_Name_2 := Chars (P_Type);
4815 Check_SPARK_05_Restriction
4816 ("attribute% is not allowed for type%", P);
4817 end if;
4819 Resolve (E1, P_Base_Type);
4820 Set_Etype (N, Universal_Integer);
4822 --------------
4823 -- Position --
4824 --------------
4826 when Attribute_Position =>
4827 Check_Component;
4828 Set_Etype (N, Universal_Integer);
4830 ----------
4831 -- Pred --
4832 ----------
4834 when Attribute_Pred =>
4835 Check_Scalar_Type;
4836 Check_E1;
4838 if Is_Real_Type (P_Type) or else Is_Boolean_Type (P_Type) then
4839 Error_Msg_Name_1 := Aname;
4840 Error_Msg_Name_2 := Chars (P_Type);
4841 Check_SPARK_05_Restriction
4842 ("attribute% is not allowed for type%", P);
4843 end if;
4845 Resolve (E1, P_Base_Type);
4846 Set_Etype (N, P_Base_Type);
4848 -- Since Pred works on the base type, we normally do no check for the
4849 -- floating-point case, since the base type is unconstrained. But we
4850 -- make an exception in Check_Float_Overflow mode.
4852 if Is_Floating_Point_Type (P_Type) then
4853 if not Range_Checks_Suppressed (P_Base_Type) then
4854 Set_Do_Range_Check (E1);
4855 end if;
4857 -- If not modular type, test for overflow check required
4859 else
4860 if not Is_Modular_Integer_Type (P_Type)
4861 and then not Range_Checks_Suppressed (P_Base_Type)
4862 then
4863 Enable_Range_Check (E1);
4864 end if;
4865 end if;
4867 --------------
4868 -- Priority --
4869 --------------
4871 -- Ada 2005 (AI-327): Dynamic ceiling priorities
4873 when Attribute_Priority =>
4874 if Ada_Version < Ada_2005 then
4875 Error_Attr ("% attribute is allowed only in Ada 2005 mode", P);
4876 end if;
4878 Check_E0;
4880 -- The prefix must be a protected object (AARM D.5.2 (2/2))
4882 Analyze (P);
4884 if Is_Protected_Type (Etype (P))
4885 or else (Is_Access_Type (Etype (P))
4886 and then Is_Protected_Type (Designated_Type (Etype (P))))
4887 then
4888 Resolve (P, Etype (P));
4889 else
4890 Error_Attr_P ("prefix of % attribute must be a protected object");
4891 end if;
4893 Set_Etype (N, Standard_Integer);
4895 -- Must be called from within a protected procedure or entry of the
4896 -- protected object.
4898 declare
4899 S : Entity_Id;
4901 begin
4902 S := Current_Scope;
4903 while S /= Etype (P)
4904 and then S /= Standard_Standard
4905 loop
4906 S := Scope (S);
4907 end loop;
4909 if S = Standard_Standard then
4910 Error_Attr ("the attribute % is only allowed inside protected "
4911 & "operations", P);
4912 end if;
4913 end;
4915 Validate_Non_Static_Attribute_Function_Call;
4917 -----------
4918 -- Range --
4919 -----------
4921 when Attribute_Range =>
4922 Check_Array_Or_Scalar_Type;
4923 Bad_Attribute_For_Predicate;
4925 if Ada_Version = Ada_83
4926 and then Is_Scalar_Type (P_Type)
4927 and then Comes_From_Source (N)
4928 then
4929 Error_Attr
4930 ("(Ada 83) % attribute not allowed for scalar type", P);
4931 end if;
4933 ------------
4934 -- Result --
4935 ------------
4937 when Attribute_Result => Result : declare
4938 CS : Entity_Id;
4939 -- The enclosing scope, excluding loops for quantified expressions
4941 PS : Entity_Id;
4942 -- During analysis, CS is the postcondition subprogram and PS the
4943 -- source subprogram to which the postcondition applies. During
4944 -- pre-analysis, CS is the scope of the subprogram declaration.
4946 Prag : Node_Id;
4947 -- During pre-analysis, Prag is the enclosing pragma node if any
4949 begin
4950 -- Find the proper enclosing scope
4952 CS := Current_Scope;
4953 while Present (CS) loop
4955 -- Skip generated loops
4957 if Ekind (CS) = E_Loop then
4958 CS := Scope (CS);
4960 -- Skip the special _Parent scope generated to capture references
4961 -- to formals during the process of subprogram inlining.
4963 elsif Ekind (CS) = E_Function
4964 and then Chars (CS) = Name_uParent
4965 then
4966 CS := Scope (CS);
4967 else
4968 exit;
4969 end if;
4970 end loop;
4972 PS := Scope (CS);
4974 -- If the enclosing subprogram is always inlined, the enclosing
4975 -- postcondition will not be propagated to the expanded call.
4977 if not In_Spec_Expression
4978 and then Has_Pragma_Inline_Always (PS)
4979 and then Warn_On_Redundant_Constructs
4980 then
4981 Error_Msg_N
4982 ("postconditions on inlined functions not enforced?r?", N);
4983 end if;
4985 -- If we are in the scope of a function and in Spec_Expression mode,
4986 -- this is likely the prescan of the postcondition (or contract case,
4987 -- or test case) pragma, and we just set the proper type. If there is
4988 -- an error it will be caught when the real Analyze call is done.
4990 if Ekind (CS) = E_Function
4991 and then In_Spec_Expression
4992 then
4993 -- Check OK prefix
4995 if Chars (CS) /= Chars (P) then
4996 Error_Msg_Name_1 := Name_Result;
4998 Error_Msg_NE
4999 ("incorrect prefix for % attribute, expected &", P, CS);
5000 Error_Attr;
5001 end if;
5003 -- Check in postcondition, Test_Case or Contract_Cases of function
5005 Prag := N;
5006 while Present (Prag)
5007 and then not Nkind_In (Prag, N_Pragma,
5008 N_Function_Specification,
5009 N_Aspect_Specification,
5010 N_Subprogram_Body)
5011 loop
5012 Prag := Parent (Prag);
5013 end loop;
5015 -- In ASIS mode, the aspect itself is analyzed, in addition to the
5016 -- corresponding pragma. Do not issue errors when analyzing the
5017 -- aspect.
5019 if Nkind (Prag) = N_Aspect_Specification then
5020 null;
5022 -- Must have a pragma
5024 elsif Nkind (Prag) /= N_Pragma then
5025 Error_Attr
5026 ("% attribute can only appear in postcondition of function",
5029 -- Processing depends on which pragma we have
5031 else
5032 case Get_Pragma_Id (Prag) is
5034 when Pragma_Test_Case =>
5035 declare
5036 Arg_Ens : constant Node_Id :=
5037 Get_Ensures_From_CTC_Pragma (Prag);
5038 Arg : Node_Id;
5040 begin
5041 Arg := N;
5042 while Arg /= Prag and then Arg /= Arg_Ens loop
5043 Arg := Parent (Arg);
5044 end loop;
5046 if Arg /= Arg_Ens then
5047 Error_Attr
5048 ("% attribute misplaced inside test case", P);
5049 end if;
5050 end;
5052 when Pragma_Contract_Cases =>
5053 declare
5054 Aggr : constant Node_Id :=
5055 Expression (First
5056 (Pragma_Argument_Associations (Prag)));
5057 Arg : Node_Id;
5059 begin
5060 Arg := N;
5061 while Arg /= Prag
5062 and then Parent (Parent (Arg)) /= Aggr
5063 loop
5064 Arg := Parent (Arg);
5065 end loop;
5067 -- At this point, Parent (Arg) should be a component
5068 -- association. Attribute Result is only allowed in
5069 -- the expression part of this association.
5071 if Nkind (Parent (Arg)) /= N_Component_Association
5072 or else Arg /= Expression (Parent (Arg))
5073 then
5074 Error_Attr
5075 ("% attribute misplaced inside contract cases",
5077 end if;
5078 end;
5080 when Pragma_Postcondition | Pragma_Refined_Post =>
5081 null;
5083 when others =>
5084 Error_Attr
5085 ("% attribute can only appear in postcondition "
5086 & "of function", P);
5087 end case;
5088 end if;
5090 -- The attribute reference is a primary. If expressions follow,
5091 -- the attribute reference is really an indexable object, so
5092 -- rewrite and analyze as an indexed component.
5094 if Present (E1) then
5095 Rewrite (N,
5096 Make_Indexed_Component (Loc,
5097 Prefix =>
5098 Make_Attribute_Reference (Loc,
5099 Prefix => Relocate_Node (Prefix (N)),
5100 Attribute_Name => Name_Result),
5101 Expressions => Expressions (N)));
5102 Analyze (N);
5103 return;
5104 end if;
5106 Set_Etype (N, Etype (CS));
5108 -- If several functions with that name are visible, the intended
5109 -- one is the current scope.
5111 if Is_Overloaded (P) then
5112 Set_Entity (P, CS);
5113 Set_Is_Overloaded (P, False);
5114 end if;
5116 -- Check the legality of attribute 'Result when it appears inside
5117 -- pragma Refined_Post. These specialized checks are required only
5118 -- when code generation is disabled. In the general case pragma
5119 -- Refined_Post is transformed into pragma Check by Process_PPCs
5120 -- which in turn is relocated to procedure _Postconditions. From
5121 -- then on the legality of 'Result is determined as usual.
5123 elsif not Expander_Active and then In_Refined_Post then
5124 PS := Current_Scope;
5126 -- The prefix denotes the proper related function
5128 if Is_Entity_Name (P)
5129 and then Ekind (Entity (P)) = E_Function
5130 and then Entity (P) = PS
5131 then
5132 null;
5134 else
5135 Error_Msg_Name_2 := Chars (PS);
5136 Error_Attr ("incorrect prefix for % attribute, expected %", P);
5137 end if;
5139 Set_Etype (N, Etype (PS));
5141 -- Body case, where we must be inside a generated _Postconditions
5142 -- procedure, and the prefix must be on the scope stack, or else the
5143 -- attribute use is definitely misplaced. The postcondition itself
5144 -- may have generated transient scopes, and is not necessarily the
5145 -- current one.
5147 else
5148 while Present (CS) and then CS /= Standard_Standard loop
5149 if Chars (CS) = Name_uPostconditions then
5150 exit;
5151 else
5152 CS := Scope (CS);
5153 end if;
5154 end loop;
5156 PS := Scope (CS);
5158 if Chars (CS) = Name_uPostconditions
5159 and then Ekind (PS) = E_Function
5160 then
5161 -- Check OK prefix
5163 if Nkind_In (P, N_Identifier, N_Operator_Symbol)
5164 and then Chars (P) = Chars (PS)
5165 then
5166 null;
5168 -- Within an instance, the prefix designates the local renaming
5169 -- of the original generic.
5171 elsif Is_Entity_Name (P)
5172 and then Ekind (Entity (P)) = E_Function
5173 and then Present (Alias (Entity (P)))
5174 and then Chars (Alias (Entity (P))) = Chars (PS)
5175 then
5176 null;
5178 else
5179 Error_Msg_Name_2 := Chars (PS);
5180 Error_Attr
5181 ("incorrect prefix for % attribute, expected %", P);
5182 end if;
5184 Rewrite (N, Make_Identifier (Sloc (N), Name_uResult));
5185 Analyze_And_Resolve (N, Etype (PS));
5187 else
5188 Error_Attr
5189 ("% attribute can only appear in postcondition of function",
5191 end if;
5192 end if;
5193 end Result;
5195 ------------------
5196 -- Range_Length --
5197 ------------------
5199 when Attribute_Range_Length =>
5200 Check_E0;
5201 Check_Discrete_Type;
5202 Set_Etype (N, Universal_Integer);
5204 ----------
5205 -- Read --
5206 ----------
5208 when Attribute_Read =>
5209 Check_E2;
5210 Check_Stream_Attribute (TSS_Stream_Read);
5211 Set_Etype (N, Standard_Void_Type);
5212 Resolve (N, Standard_Void_Type);
5213 Note_Possible_Modification (E2, Sure => True);
5215 ---------
5216 -- Ref --
5217 ---------
5219 when Attribute_Ref =>
5220 Check_E1;
5221 Analyze (P);
5223 if Nkind (P) /= N_Expanded_Name
5224 or else not Is_RTE (P_Type, RE_Address)
5225 then
5226 Error_Attr_P ("prefix of % attribute must be System.Address");
5227 end if;
5229 Analyze_And_Resolve (E1, Any_Integer);
5230 Set_Etype (N, RTE (RE_Address));
5232 ---------------
5233 -- Remainder --
5234 ---------------
5236 when Attribute_Remainder =>
5237 Check_Floating_Point_Type_2;
5238 Set_Etype (N, P_Base_Type);
5239 Resolve (E1, P_Base_Type);
5240 Resolve (E2, P_Base_Type);
5242 ---------------------
5243 -- Restriction_Set --
5244 ---------------------
5246 when Attribute_Restriction_Set => Restriction_Set : declare
5247 R : Restriction_Id;
5248 U : Node_Id;
5249 Unam : Unit_Name_Type;
5251 begin
5252 Check_E1;
5253 Analyze (P);
5254 Check_System_Prefix;
5256 -- No_Dependence case
5258 if Nkind (E1) = N_Parameter_Association then
5259 pragma Assert (Chars (Selector_Name (E1)) = Name_No_Dependence);
5260 U := Explicit_Actual_Parameter (E1);
5262 if not OK_No_Dependence_Unit_Name (U) then
5263 Set_Boolean_Result (N, False);
5264 Error_Attr;
5265 end if;
5267 -- See if there is an entry already in the table. That's the
5268 -- case in which we can return True.
5270 for J in No_Dependences.First .. No_Dependences.Last loop
5271 if Designate_Same_Unit (U, No_Dependences.Table (J).Unit)
5272 and then No_Dependences.Table (J).Warn = False
5273 then
5274 Set_Boolean_Result (N, True);
5275 return;
5276 end if;
5277 end loop;
5279 -- If not in the No_Dependence table, result is False
5281 Set_Boolean_Result (N, False);
5283 -- In this case, we must ensure that the binder will reject any
5284 -- other unit in the partition that sets No_Dependence for this
5285 -- unit. We do that by making an entry in the special table kept
5286 -- for this purpose (if the entry is not there already).
5288 Unam := Get_Spec_Name (Get_Unit_Name (U));
5290 for J in Restriction_Set_Dependences.First ..
5291 Restriction_Set_Dependences.Last
5292 loop
5293 if Restriction_Set_Dependences.Table (J) = Unam then
5294 return;
5295 end if;
5296 end loop;
5298 Restriction_Set_Dependences.Append (Unam);
5300 -- Normal restriction case
5302 else
5303 if Nkind (E1) /= N_Identifier then
5304 Set_Boolean_Result (N, False);
5305 Error_Attr ("attribute % requires restriction identifier", E1);
5307 else
5308 R := Get_Restriction_Id (Process_Restriction_Synonyms (E1));
5310 if R = Not_A_Restriction_Id then
5311 Set_Boolean_Result (N, False);
5312 Error_Msg_Node_1 := E1;
5313 Error_Attr ("invalid restriction identifier &", E1);
5315 elsif R not in Partition_Boolean_Restrictions then
5316 Set_Boolean_Result (N, False);
5317 Error_Msg_Node_1 := E1;
5318 Error_Attr
5319 ("& is not a boolean partition-wide restriction", E1);
5320 end if;
5322 if Restriction_Active (R) then
5323 Set_Boolean_Result (N, True);
5324 else
5325 Check_Restriction (R, N);
5326 Set_Boolean_Result (N, False);
5327 end if;
5328 end if;
5329 end if;
5330 end Restriction_Set;
5332 -----------
5333 -- Round --
5334 -----------
5336 when Attribute_Round =>
5337 Check_E1;
5338 Check_Decimal_Fixed_Point_Type;
5339 Set_Etype (N, P_Base_Type);
5341 -- Because the context is universal_real (3.5.10(12)) it is a
5342 -- legal context for a universal fixed expression. This is the
5343 -- only attribute whose functional description involves U_R.
5345 if Etype (E1) = Universal_Fixed then
5346 declare
5347 Conv : constant Node_Id := Make_Type_Conversion (Loc,
5348 Subtype_Mark => New_Occurrence_Of (Universal_Real, Loc),
5349 Expression => Relocate_Node (E1));
5351 begin
5352 Rewrite (E1, Conv);
5353 Analyze (E1);
5354 end;
5355 end if;
5357 Resolve (E1, Any_Real);
5359 --------------
5360 -- Rounding --
5361 --------------
5363 when Attribute_Rounding =>
5364 Check_Floating_Point_Type_1;
5365 Set_Etype (N, P_Base_Type);
5366 Resolve (E1, P_Base_Type);
5368 ---------------
5369 -- Safe_Emax --
5370 ---------------
5372 when Attribute_Safe_Emax =>
5373 Check_Floating_Point_Type_0;
5374 Set_Etype (N, Universal_Integer);
5376 ----------------
5377 -- Safe_First --
5378 ----------------
5380 when Attribute_Safe_First =>
5381 Check_Floating_Point_Type_0;
5382 Set_Etype (N, Universal_Real);
5384 ----------------
5385 -- Safe_Large --
5386 ----------------
5388 when Attribute_Safe_Large =>
5389 Check_E0;
5390 Check_Real_Type;
5391 Set_Etype (N, Universal_Real);
5393 ---------------
5394 -- Safe_Last --
5395 ---------------
5397 when Attribute_Safe_Last =>
5398 Check_Floating_Point_Type_0;
5399 Set_Etype (N, Universal_Real);
5401 ----------------
5402 -- Safe_Small --
5403 ----------------
5405 when Attribute_Safe_Small =>
5406 Check_E0;
5407 Check_Real_Type;
5408 Set_Etype (N, Universal_Real);
5410 --------------------------
5411 -- Scalar_Storage_Order --
5412 --------------------------
5414 when Attribute_Scalar_Storage_Order => Scalar_Storage_Order :
5415 declare
5416 Ent : Entity_Id := Empty;
5418 begin
5419 Check_E0;
5420 Check_Type;
5422 if not (Is_Record_Type (P_Type) or else Is_Array_Type (P_Type)) then
5424 -- In GNAT mode, the attribute applies to generic types as well
5425 -- as composite types, and for non-composite types always returns
5426 -- the default bit order for the target.
5428 if not (GNAT_Mode and then Is_Generic_Type (P_Type))
5429 and then not In_Instance
5430 then
5431 Error_Attr_P
5432 ("prefix of % attribute must be record or array type");
5434 elsif not Is_Generic_Type (P_Type) then
5435 if Bytes_Big_Endian then
5436 Ent := RTE (RE_High_Order_First);
5437 else
5438 Ent := RTE (RE_Low_Order_First);
5439 end if;
5440 end if;
5442 elsif Bytes_Big_Endian xor Reverse_Storage_Order (P_Type) then
5443 Ent := RTE (RE_High_Order_First);
5445 else
5446 Ent := RTE (RE_Low_Order_First);
5447 end if;
5449 if Present (Ent) then
5450 Rewrite (N, New_Occurrence_Of (Ent, Loc));
5451 end if;
5453 Set_Etype (N, RTE (RE_Bit_Order));
5454 Resolve (N);
5456 -- Reset incorrect indication of staticness
5458 Set_Is_Static_Expression (N, False);
5459 end Scalar_Storage_Order;
5461 -----------
5462 -- Scale --
5463 -----------
5465 when Attribute_Scale =>
5466 Check_E0;
5467 Check_Decimal_Fixed_Point_Type;
5468 Set_Etype (N, Universal_Integer);
5470 -------------
5471 -- Scaling --
5472 -------------
5474 when Attribute_Scaling =>
5475 Check_Floating_Point_Type_2;
5476 Set_Etype (N, P_Base_Type);
5477 Resolve (E1, P_Base_Type);
5479 ------------------
5480 -- Signed_Zeros --
5481 ------------------
5483 when Attribute_Signed_Zeros =>
5484 Check_Floating_Point_Type_0;
5485 Set_Etype (N, Standard_Boolean);
5487 ----------
5488 -- Size --
5489 ----------
5491 when Attribute_Size | Attribute_VADS_Size => Size :
5492 begin
5493 Check_E0;
5495 -- If prefix is parameterless function call, rewrite and resolve
5496 -- as such.
5498 if Is_Entity_Name (P)
5499 and then Ekind (Entity (P)) = E_Function
5500 then
5501 Resolve (P);
5503 -- Similar processing for a protected function call
5505 elsif Nkind (P) = N_Selected_Component
5506 and then Ekind (Entity (Selector_Name (P))) = E_Function
5507 then
5508 Resolve (P);
5509 end if;
5511 if Is_Object_Reference (P) then
5512 Check_Object_Reference (P);
5514 elsif Is_Entity_Name (P)
5515 and then (Is_Type (Entity (P))
5516 or else Ekind (Entity (P)) = E_Enumeration_Literal)
5517 then
5518 null;
5520 elsif Nkind (P) = N_Type_Conversion
5521 and then not Comes_From_Source (P)
5522 then
5523 null;
5525 -- Some other compilers allow dubious use of X'???'Size
5527 elsif Relaxed_RM_Semantics
5528 and then Nkind (P) = N_Attribute_Reference
5529 then
5530 null;
5532 else
5533 Error_Attr_P ("invalid prefix for % attribute");
5534 end if;
5536 Check_Not_Incomplete_Type;
5537 Check_Not_CPP_Type;
5538 Set_Etype (N, Universal_Integer);
5539 end Size;
5541 -----------
5542 -- Small --
5543 -----------
5545 when Attribute_Small =>
5546 Check_E0;
5547 Check_Real_Type;
5548 Set_Etype (N, Universal_Real);
5550 ------------------
5551 -- Storage_Pool --
5552 ------------------
5554 when Attribute_Storage_Pool |
5555 Attribute_Simple_Storage_Pool => Storage_Pool :
5556 begin
5557 Check_E0;
5559 if Is_Access_Type (P_Type) then
5560 if Ekind (P_Type) = E_Access_Subprogram_Type then
5561 Error_Attr_P
5562 ("cannot use % attribute for access-to-subprogram type");
5563 end if;
5565 -- Set appropriate entity
5567 if Present (Associated_Storage_Pool (Root_Type (P_Type))) then
5568 Set_Entity (N, Associated_Storage_Pool (Root_Type (P_Type)));
5569 else
5570 Set_Entity (N, RTE (RE_Global_Pool_Object));
5571 end if;
5573 if Attr_Id = Attribute_Storage_Pool then
5574 if Present (Get_Rep_Pragma (Etype (Entity (N)),
5575 Name_Simple_Storage_Pool_Type))
5576 then
5577 Error_Msg_Name_1 := Aname;
5578 Error_Msg_Warn := SPARK_Mode /= On;
5579 Error_Msg_N ("cannot use % attribute for type with simple "
5580 & "storage pool<<", N);
5581 Error_Msg_N ("\Program_Error [<<", N);
5583 Rewrite
5584 (N, Make_Raise_Program_Error
5585 (Sloc (N), Reason => PE_Explicit_Raise));
5586 end if;
5588 Set_Etype (N, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
5590 -- In the Simple_Storage_Pool case, verify that the pool entity is
5591 -- actually of a simple storage pool type, and set the attribute's
5592 -- type to the pool object's type.
5594 else
5595 if not Present (Get_Rep_Pragma (Etype (Entity (N)),
5596 Name_Simple_Storage_Pool_Type))
5597 then
5598 Error_Attr_P
5599 ("cannot use % attribute for type without simple " &
5600 "storage pool");
5601 end if;
5603 Set_Etype (N, Etype (Entity (N)));
5604 end if;
5606 -- Validate_Remote_Access_To_Class_Wide_Type for attribute
5607 -- Storage_Pool since this attribute is not defined for such
5608 -- types (RM E.2.3(22)).
5610 Validate_Remote_Access_To_Class_Wide_Type (N);
5612 else
5613 Error_Attr_P ("prefix of % attribute must be access type");
5614 end if;
5615 end Storage_Pool;
5617 ------------------
5618 -- Storage_Size --
5619 ------------------
5621 when Attribute_Storage_Size => Storage_Size :
5622 begin
5623 Check_E0;
5625 if Is_Task_Type (P_Type) then
5626 Set_Etype (N, Universal_Integer);
5628 -- Use with tasks is an obsolescent feature
5630 Check_Restriction (No_Obsolescent_Features, P);
5632 elsif Is_Access_Type (P_Type) then
5633 if Ekind (P_Type) = E_Access_Subprogram_Type then
5634 Error_Attr_P
5635 ("cannot use % attribute for access-to-subprogram type");
5636 end if;
5638 if Is_Entity_Name (P)
5639 and then Is_Type (Entity (P))
5640 then
5641 Check_Type;
5642 Set_Etype (N, Universal_Integer);
5644 -- Validate_Remote_Access_To_Class_Wide_Type for attribute
5645 -- Storage_Size since this attribute is not defined for
5646 -- such types (RM E.2.3(22)).
5648 Validate_Remote_Access_To_Class_Wide_Type (N);
5650 -- The prefix is allowed to be an implicit dereference of an
5651 -- access value designating a task.
5653 else
5654 Check_Task_Prefix;
5655 Set_Etype (N, Universal_Integer);
5656 end if;
5658 else
5659 Error_Attr_P ("prefix of % attribute must be access or task type");
5660 end if;
5661 end Storage_Size;
5663 ------------------
5664 -- Storage_Unit --
5665 ------------------
5667 when Attribute_Storage_Unit =>
5668 Standard_Attribute (Ttypes.System_Storage_Unit);
5670 -----------------
5671 -- Stream_Size --
5672 -----------------
5674 when Attribute_Stream_Size =>
5675 Check_E0;
5676 Check_Type;
5678 if Is_Entity_Name (P)
5679 and then Is_Elementary_Type (Entity (P))
5680 then
5681 Set_Etype (N, Universal_Integer);
5682 else
5683 Error_Attr_P ("invalid prefix for % attribute");
5684 end if;
5686 ---------------
5687 -- Stub_Type --
5688 ---------------
5690 when Attribute_Stub_Type =>
5691 Check_Type;
5692 Check_E0;
5694 if Is_Remote_Access_To_Class_Wide_Type (Base_Type (P_Type)) then
5696 -- For a real RACW [sub]type, use corresponding stub type
5698 if not Is_Generic_Type (P_Type) then
5699 Rewrite (N,
5700 New_Occurrence_Of
5701 (Corresponding_Stub_Type (Base_Type (P_Type)), Loc));
5703 -- For a generic type (that has been marked as an RACW using the
5704 -- Remote_Access_Type aspect or pragma), use a generic RACW stub
5705 -- type. Note that if the actual is not a remote access type, the
5706 -- instantiation will fail.
5708 else
5709 -- Note: we go to the underlying type here because the view
5710 -- returned by RTE (RE_RACW_Stub_Type) might be incomplete.
5712 Rewrite (N,
5713 New_Occurrence_Of
5714 (Underlying_Type (RTE (RE_RACW_Stub_Type)), Loc));
5715 end if;
5717 else
5718 Error_Attr_P
5719 ("prefix of% attribute must be remote access to classwide");
5720 end if;
5722 ----------
5723 -- Succ --
5724 ----------
5726 when Attribute_Succ =>
5727 Check_Scalar_Type;
5728 Check_E1;
5730 if Is_Real_Type (P_Type) or else Is_Boolean_Type (P_Type) then
5731 Error_Msg_Name_1 := Aname;
5732 Error_Msg_Name_2 := Chars (P_Type);
5733 Check_SPARK_05_Restriction
5734 ("attribute% is not allowed for type%", P);
5735 end if;
5737 Resolve (E1, P_Base_Type);
5738 Set_Etype (N, P_Base_Type);
5740 -- Since Pred works on the base type, we normally do no check for the
5741 -- floating-point case, since the base type is unconstrained. But we
5742 -- make an exception in Check_Float_Overflow mode.
5744 if Is_Floating_Point_Type (P_Type) then
5745 if not Range_Checks_Suppressed (P_Base_Type) then
5746 Set_Do_Range_Check (E1);
5747 end if;
5749 -- If not modular type, test for overflow check required
5751 else
5752 if not Is_Modular_Integer_Type (P_Type)
5753 and then not Range_Checks_Suppressed (P_Base_Type)
5754 then
5755 Enable_Range_Check (E1);
5756 end if;
5757 end if;
5759 --------------------------------
5760 -- System_Allocator_Alignment --
5761 --------------------------------
5763 when Attribute_System_Allocator_Alignment =>
5764 Standard_Attribute (Ttypes.System_Allocator_Alignment);
5766 ---------
5767 -- Tag --
5768 ---------
5770 when Attribute_Tag => Tag :
5771 begin
5772 Check_E0;
5773 Check_Dereference;
5775 if not Is_Tagged_Type (P_Type) then
5776 Error_Attr_P ("prefix of % attribute must be tagged");
5778 -- Next test does not apply to generated code why not, and what does
5779 -- the illegal reference mean???
5781 elsif Is_Object_Reference (P)
5782 and then not Is_Class_Wide_Type (P_Type)
5783 and then Comes_From_Source (N)
5784 then
5785 Error_Attr_P
5786 ("% attribute can only be applied to objects " &
5787 "of class - wide type");
5788 end if;
5790 -- The prefix cannot be an incomplete type. However, references to
5791 -- 'Tag can be generated when expanding interface conversions, and
5792 -- this is legal.
5794 if Comes_From_Source (N) then
5795 Check_Not_Incomplete_Type;
5796 end if;
5798 -- Set appropriate type
5800 Set_Etype (N, RTE (RE_Tag));
5801 end Tag;
5803 -----------------
5804 -- Target_Name --
5805 -----------------
5807 when Attribute_Target_Name => Target_Name : declare
5808 TN : constant String := Sdefault.Target_Name.all;
5809 TL : Natural;
5811 begin
5812 Check_Standard_Prefix;
5814 TL := TN'Last;
5816 if TN (TL) = '/' or else TN (TL) = '\' then
5817 TL := TL - 1;
5818 end if;
5820 Rewrite (N,
5821 Make_String_Literal (Loc,
5822 Strval => TN (TN'First .. TL)));
5823 Analyze_And_Resolve (N, Standard_String);
5824 Set_Is_Static_Expression (N, True);
5825 end Target_Name;
5827 ----------------
5828 -- Terminated --
5829 ----------------
5831 when Attribute_Terminated =>
5832 Check_E0;
5833 Set_Etype (N, Standard_Boolean);
5834 Check_Task_Prefix;
5836 ----------------
5837 -- To_Address --
5838 ----------------
5840 when Attribute_To_Address => To_Address : declare
5841 Val : Uint;
5843 begin
5844 Check_E1;
5845 Analyze (P);
5846 Check_System_Prefix;
5848 Generate_Reference (RTE (RE_Address), P);
5849 Analyze_And_Resolve (E1, Any_Integer);
5850 Set_Etype (N, RTE (RE_Address));
5852 if Is_Static_Expression (E1) then
5853 Set_Is_Static_Expression (N, True);
5854 end if;
5856 -- OK static expression case, check range and set appropriate type
5858 if Is_OK_Static_Expression (E1) then
5859 Val := Expr_Value (E1);
5861 if Val < -(2 ** UI_From_Int (Standard'Address_Size - 1))
5862 or else
5863 Val > 2 ** UI_From_Int (Standard'Address_Size) - 1
5864 then
5865 Error_Attr ("address value out of range for % attribute", E1);
5866 end if;
5868 -- In most cases the expression is a numeric literal or some other
5869 -- address expression, but if it is a declared constant it may be
5870 -- of a compatible type that must be left on the node.
5872 if Is_Entity_Name (E1) then
5873 null;
5875 -- Set type to universal integer if negative
5877 elsif Val < 0 then
5878 Set_Etype (E1, Universal_Integer);
5880 -- Otherwise set type to Unsigned_64 to accomodate max values
5882 else
5883 Set_Etype (E1, Standard_Unsigned_64);
5884 end if;
5885 end if;
5887 Set_Is_Static_Expression (N, True);
5888 end To_Address;
5890 ------------
5891 -- To_Any --
5892 ------------
5894 when Attribute_To_Any =>
5895 Check_E1;
5896 Check_PolyORB_Attribute;
5897 Set_Etype (N, RTE (RE_Any));
5899 ----------------
5900 -- Truncation --
5901 ----------------
5903 when Attribute_Truncation =>
5904 Check_Floating_Point_Type_1;
5905 Resolve (E1, P_Base_Type);
5906 Set_Etype (N, P_Base_Type);
5908 ----------------
5909 -- Type_Class --
5910 ----------------
5912 when Attribute_Type_Class =>
5913 Check_E0;
5914 Check_Type;
5915 Check_Not_Incomplete_Type;
5916 Set_Etype (N, RTE (RE_Type_Class));
5918 --------------
5919 -- TypeCode --
5920 --------------
5922 when Attribute_TypeCode =>
5923 Check_E0;
5924 Check_PolyORB_Attribute;
5925 Set_Etype (N, RTE (RE_TypeCode));
5927 --------------
5928 -- Type_Key --
5929 --------------
5931 when Attribute_Type_Key =>
5932 Check_E0;
5933 Check_Type;
5935 -- This processing belongs in Eval_Attribute ???
5937 declare
5938 function Type_Key return String_Id;
5939 -- A very preliminary implementation. For now, a signature
5940 -- consists of only the type name. This is clearly incomplete
5941 -- (e.g., adding a new field to a record type should change the
5942 -- type's Type_Key attribute).
5944 --------------
5945 -- Type_Key --
5946 --------------
5948 function Type_Key return String_Id is
5949 Full_Name : constant String_Id :=
5950 Fully_Qualified_Name_String (Entity (P));
5952 begin
5953 -- Copy all characters in Full_Name but the trailing NUL
5955 Start_String;
5956 for J in 1 .. String_Length (Full_Name) - 1 loop
5957 Store_String_Char (Get_String_Char (Full_Name, Int (J)));
5958 end loop;
5960 Store_String_Chars ("'Type_Key");
5961 return End_String;
5962 end Type_Key;
5964 begin
5965 Rewrite (N, Make_String_Literal (Loc, Type_Key));
5966 end;
5968 Analyze_And_Resolve (N, Standard_String);
5970 -----------------
5971 -- UET_Address --
5972 -----------------
5974 when Attribute_UET_Address =>
5975 Check_E0;
5976 Check_Unit_Name (P);
5977 Set_Etype (N, RTE (RE_Address));
5979 -----------------------
5980 -- Unbiased_Rounding --
5981 -----------------------
5983 when Attribute_Unbiased_Rounding =>
5984 Check_Floating_Point_Type_1;
5985 Set_Etype (N, P_Base_Type);
5986 Resolve (E1, P_Base_Type);
5988 ----------------------
5989 -- Unchecked_Access --
5990 ----------------------
5992 when Attribute_Unchecked_Access =>
5993 if Comes_From_Source (N) then
5994 Check_Restriction (No_Unchecked_Access, N);
5995 end if;
5997 Analyze_Access_Attribute;
5999 -------------------------
6000 -- Unconstrained_Array --
6001 -------------------------
6003 when Attribute_Unconstrained_Array =>
6004 Check_E0;
6005 Check_Type;
6006 Check_Not_Incomplete_Type;
6007 Set_Etype (N, Standard_Boolean);
6008 Set_Is_Static_Expression (N, True);
6010 ------------------------------
6011 -- Universal_Literal_String --
6012 ------------------------------
6014 -- This is a GNAT specific attribute whose prefix must be a named
6015 -- number where the expression is either a single numeric literal,
6016 -- or a numeric literal immediately preceded by a minus sign. The
6017 -- result is equivalent to a string literal containing the text of
6018 -- the literal as it appeared in the source program with a possible
6019 -- leading minus sign.
6021 when Attribute_Universal_Literal_String => Universal_Literal_String :
6022 begin
6023 Check_E0;
6025 if not Is_Entity_Name (P)
6026 or else Ekind (Entity (P)) not in Named_Kind
6027 then
6028 Error_Attr_P ("prefix for % attribute must be named number");
6030 else
6031 declare
6032 Expr : Node_Id;
6033 Negative : Boolean;
6034 S : Source_Ptr;
6035 Src : Source_Buffer_Ptr;
6037 begin
6038 Expr := Original_Node (Expression (Parent (Entity (P))));
6040 if Nkind (Expr) = N_Op_Minus then
6041 Negative := True;
6042 Expr := Original_Node (Right_Opnd (Expr));
6043 else
6044 Negative := False;
6045 end if;
6047 if not Nkind_In (Expr, N_Integer_Literal, N_Real_Literal) then
6048 Error_Attr
6049 ("named number for % attribute must be simple literal", N);
6050 end if;
6052 -- Build string literal corresponding to source literal text
6054 Start_String;
6056 if Negative then
6057 Store_String_Char (Get_Char_Code ('-'));
6058 end if;
6060 S := Sloc (Expr);
6061 Src := Source_Text (Get_Source_File_Index (S));
6063 while Src (S) /= ';' and then Src (S) /= ' ' loop
6064 Store_String_Char (Get_Char_Code (Src (S)));
6065 S := S + 1;
6066 end loop;
6068 -- Now we rewrite the attribute with the string literal
6070 Rewrite (N,
6071 Make_String_Literal (Loc, End_String));
6072 Analyze (N);
6073 Set_Is_Static_Expression (N, True);
6074 end;
6075 end if;
6076 end Universal_Literal_String;
6078 -------------------------
6079 -- Unrestricted_Access --
6080 -------------------------
6082 -- This is a GNAT specific attribute which is like Access except that
6083 -- all scope checks and checks for aliased views are omitted. It is
6084 -- documented as being equivalent to the use of the Address attribute
6085 -- followed by an unchecked conversion to the target access type.
6087 when Attribute_Unrestricted_Access =>
6089 -- If from source, deal with relevant restrictions
6091 if Comes_From_Source (N) then
6092 Check_Restriction (No_Unchecked_Access, N);
6094 if Nkind (P) in N_Has_Entity
6095 and then Present (Entity (P))
6096 and then Is_Object (Entity (P))
6097 then
6098 Check_Restriction (No_Implicit_Aliasing, N);
6099 end if;
6100 end if;
6102 if Is_Entity_Name (P) then
6103 Set_Address_Taken (Entity (P));
6104 end if;
6106 -- It might seem reasonable to call Address_Checks here to apply the
6107 -- same set of semantic checks that we enforce for 'Address (after
6108 -- all we document Unrestricted_Access as being equivalent to the
6109 -- use of Address followed by an Unchecked_Conversion). However, if
6110 -- we do enable these checks, we get multiple failures in both the
6111 -- compiler run-time and in our regression test suite, so we leave
6112 -- out these checks for now. To be investigated further some time???
6114 -- Address_Checks;
6116 -- Now complete analysis using common access processing
6118 Analyze_Access_Attribute;
6120 ------------
6121 -- Update --
6122 ------------
6124 when Attribute_Update => Update : declare
6125 Common_Typ : Entity_Id;
6126 -- The common type of a multiple component update for a record
6128 Comps : Elist_Id := No_Elist;
6129 -- A list used in the resolution of a record update. It contains the
6130 -- entities of all record components processed so far.
6132 procedure Analyze_Array_Component_Update (Assoc : Node_Id);
6133 -- Analyze and resolve array_component_association Assoc against the
6134 -- index of array type P_Type.
6136 procedure Analyze_Record_Component_Update (Comp : Node_Id);
6137 -- Analyze and resolve record_component_association Comp against
6138 -- record type P_Type.
6140 ------------------------------------
6141 -- Analyze_Array_Component_Update --
6142 ------------------------------------
6144 procedure Analyze_Array_Component_Update (Assoc : Node_Id) is
6145 Expr : Node_Id;
6146 High : Node_Id;
6147 Index : Node_Id;
6148 Index_Typ : Entity_Id;
6149 Low : Node_Id;
6151 begin
6152 -- The current association contains a sequence of indexes denoting
6153 -- an element of a multidimensional array:
6155 -- (Index_1, ..., Index_N)
6157 -- Examine each individual index and resolve it against the proper
6158 -- index type of the array.
6160 if Nkind (First (Choices (Assoc))) = N_Aggregate then
6161 Expr := First (Choices (Assoc));
6162 while Present (Expr) loop
6164 -- The use of others is illegal (SPARK RM 4.4.1(12))
6166 if Nkind (Expr) = N_Others_Choice then
6167 Error_Attr
6168 ("others choice not allowed in attribute %", Expr);
6170 -- Otherwise analyze and resolve all indexes
6172 else
6173 Index := First (Expressions (Expr));
6174 Index_Typ := First_Index (P_Type);
6175 while Present (Index) and then Present (Index_Typ) loop
6176 Analyze_And_Resolve (Index, Etype (Index_Typ));
6177 Next (Index);
6178 Next_Index (Index_Typ);
6179 end loop;
6181 -- Detect a case where the association either lacks an
6182 -- index or contains an extra index.
6184 if Present (Index) or else Present (Index_Typ) then
6185 Error_Msg_N
6186 ("dimension mismatch in index list", Assoc);
6187 end if;
6188 end if;
6190 Next (Expr);
6191 end loop;
6193 -- The current association denotes either a single component or a
6194 -- range of components of a one dimensional array:
6196 -- 1, 2 .. 5
6198 -- Resolve the index or its high and low bounds (if range) against
6199 -- the proper index type of the array.
6201 else
6202 Index := First (Choices (Assoc));
6203 Index_Typ := First_Index (P_Type);
6205 if Present (Next_Index (Index_Typ)) then
6206 Error_Msg_N ("too few subscripts in array reference", Assoc);
6207 end if;
6209 while Present (Index) loop
6211 -- The use of others is illegal (SPARK RM 4.4.1(12))
6213 if Nkind (Index) = N_Others_Choice then
6214 Error_Attr
6215 ("others choice not allowed in attribute %", Index);
6217 -- The index denotes a range of elements
6219 elsif Nkind (Index) = N_Range then
6220 Low := Low_Bound (Index);
6221 High := High_Bound (Index);
6223 Analyze_And_Resolve (Low, Etype (Index_Typ));
6224 Analyze_And_Resolve (High, Etype (Index_Typ));
6226 -- Add a range check to ensure that the bounds of the
6227 -- range are within the index type when this cannot be
6228 -- determined statically.
6230 if not Is_OK_Static_Expression (Low) then
6231 Set_Do_Range_Check (Low);
6232 end if;
6234 if not Is_OK_Static_Expression (High) then
6235 Set_Do_Range_Check (High);
6236 end if;
6238 -- Otherwise the index denotes a single element
6240 else
6241 Analyze_And_Resolve (Index, Etype (Index_Typ));
6243 -- Add a range check to ensure that the index is within
6244 -- the index type when it is not possible to determine
6245 -- this statically.
6247 if not Is_OK_Static_Expression (Index) then
6248 Set_Do_Range_Check (Index);
6249 end if;
6250 end if;
6252 Next (Index);
6253 end loop;
6254 end if;
6255 end Analyze_Array_Component_Update;
6257 -------------------------------------
6258 -- Analyze_Record_Component_Update --
6259 -------------------------------------
6261 procedure Analyze_Record_Component_Update (Comp : Node_Id) is
6262 Comp_Name : constant Name_Id := Chars (Comp);
6263 Base_Typ : Entity_Id;
6264 Comp_Or_Discr : Entity_Id;
6266 begin
6267 -- Find the discriminant or component whose name corresponds to
6268 -- Comp. A simple character comparison is sufficient because all
6269 -- visible names within a record type are unique.
6271 Comp_Or_Discr := First_Entity (P_Type);
6272 while Present (Comp_Or_Discr) loop
6273 if Chars (Comp_Or_Discr) = Comp_Name then
6275 -- Decorate the component reference by setting its entity
6276 -- and type for resolution purposes.
6278 Set_Entity (Comp, Comp_Or_Discr);
6279 Set_Etype (Comp, Etype (Comp_Or_Discr));
6280 exit;
6281 end if;
6283 Comp_Or_Discr := Next_Entity (Comp_Or_Discr);
6284 end loop;
6286 -- Diagnose an illegal reference
6288 if Present (Comp_Or_Discr) then
6289 if Ekind (Comp_Or_Discr) = E_Discriminant then
6290 Error_Attr
6291 ("attribute % may not modify record discriminants", Comp);
6293 else pragma Assert (Ekind (Comp_Or_Discr) = E_Component);
6294 if Contains (Comps, Comp_Or_Discr) then
6295 Error_Msg_N ("component & already updated", Comp);
6297 -- Mark this component as processed
6299 else
6300 Append_New_Elmt (Comp_Or_Discr, Comps);
6301 end if;
6302 end if;
6304 -- The update aggregate mentions an entity that does not belong to
6305 -- the record type.
6307 else
6308 Error_Msg_N ("& is not a component of aggregate subtype", Comp);
6309 end if;
6311 -- Verify the consistency of types when the current component is
6312 -- part of a miltiple component update.
6314 -- Comp_1, ..., Comp_N => <value>
6316 if Present (Etype (Comp)) then
6317 Base_Typ := Base_Type (Etype (Comp));
6319 -- Save the type of the first component reference as the
6320 -- remaning references (if any) must resolve to this type.
6322 if No (Common_Typ) then
6323 Common_Typ := Base_Typ;
6325 elsif Base_Typ /= Common_Typ then
6326 Error_Msg_N
6327 ("components in choice list must have same type", Comp);
6328 end if;
6329 end if;
6330 end Analyze_Record_Component_Update;
6332 -- Local variables
6334 Assoc : Node_Id;
6335 Comp : Node_Id;
6337 -- Start of processing for Update
6339 begin
6340 Check_E1;
6342 if not Is_Object_Reference (P) then
6343 Error_Attr_P ("prefix of attribute % must denote an object");
6345 elsif not Is_Array_Type (P_Type)
6346 and then not Is_Record_Type (P_Type)
6347 then
6348 Error_Attr_P ("prefix of attribute % must be a record or array");
6350 elsif Is_Limited_View (P_Type) then
6351 Error_Attr ("prefix of attribute % cannot be limited", N);
6353 elsif Nkind (E1) /= N_Aggregate then
6354 Error_Attr ("attribute % requires component association list", N);
6355 end if;
6357 -- Inspect the update aggregate, looking at all the associations and
6358 -- choices. Perform the following checks:
6360 -- 1) Legality of "others" in all cases
6361 -- 2) Legality of <>
6362 -- 3) Component legality for arrays
6363 -- 4) Component legality for records
6365 -- The remaining checks are performed on the expanded attribute
6367 Assoc := First (Component_Associations (E1));
6368 while Present (Assoc) loop
6370 -- The use of <> is illegal (SPARK RM 4.4.1(1))
6372 if Box_Present (Assoc) then
6373 Error_Attr
6374 ("default initialization not allowed in attribute %", Assoc);
6376 -- Otherwise process the association
6378 else
6379 Analyze (Expression (Assoc));
6381 if Is_Array_Type (P_Type) then
6382 Analyze_Array_Component_Update (Assoc);
6384 elsif Is_Record_Type (P_Type) then
6386 -- Reset the common type used in a multiple component update
6387 -- as we are processing the contents of a new association.
6389 Common_Typ := Empty;
6391 Comp := First (Choices (Assoc));
6392 while Present (Comp) loop
6393 if Nkind (Comp) = N_Identifier then
6394 Analyze_Record_Component_Update (Comp);
6396 -- The use of others is illegal (SPARK RM 4.4.1(5))
6398 elsif Nkind (Comp) = N_Others_Choice then
6399 Error_Attr
6400 ("others choice not allowed in attribute %", Comp);
6402 -- The name of a record component cannot appear in any
6403 -- other form.
6405 else
6406 Error_Msg_N
6407 ("name should be identifier or OTHERS", Comp);
6408 end if;
6410 Next (Comp);
6411 end loop;
6412 end if;
6413 end if;
6415 Next (Assoc);
6416 end loop;
6418 -- The type of attribute 'Update is that of the prefix
6420 Set_Etype (N, P_Type);
6421 end Update;
6423 ---------
6424 -- Val --
6425 ---------
6427 when Attribute_Val => Val : declare
6428 begin
6429 Check_E1;
6430 Check_Discrete_Type;
6432 if Is_Boolean_Type (P_Type) then
6433 Error_Msg_Name_1 := Aname;
6434 Error_Msg_Name_2 := Chars (P_Type);
6435 Check_SPARK_05_Restriction
6436 ("attribute% is not allowed for type%", P);
6437 end if;
6439 Resolve (E1, Any_Integer);
6440 Set_Etype (N, P_Base_Type);
6442 -- Note, we need a range check in general, but we wait for the
6443 -- Resolve call to do this, since we want to let Eval_Attribute
6444 -- have a chance to find an static illegality first.
6445 end Val;
6447 -----------
6448 -- Valid --
6449 -----------
6451 when Attribute_Valid =>
6452 Check_E0;
6454 -- Ignore check for object if we have a 'Valid reference generated
6455 -- by the expanded code, since in some cases valid checks can occur
6456 -- on items that are names, but are not objects (e.g. attributes).
6458 if Comes_From_Source (N) then
6459 Check_Object_Reference (P);
6460 end if;
6462 if not Is_Scalar_Type (P_Type) then
6463 Error_Attr_P ("object for % attribute must be of scalar type");
6464 end if;
6466 -- If the attribute appears within the subtype's own predicate
6467 -- function, then issue a warning that this will cause infinite
6468 -- recursion.
6470 declare
6471 Pred_Func : constant Entity_Id := Predicate_Function (P_Type);
6473 begin
6474 if Present (Pred_Func) and then Current_Scope = Pred_Func then
6475 Error_Msg_N
6476 ("attribute Valid requires a predicate check??", N);
6477 Error_Msg_N ("\and will result in infinite recursion??", N);
6478 end if;
6479 end;
6481 Set_Etype (N, Standard_Boolean);
6483 -------------------
6484 -- Valid_Scalars --
6485 -------------------
6487 when Attribute_Valid_Scalars =>
6488 Check_E0;
6489 Check_Object_Reference (P);
6490 Set_Etype (N, Standard_Boolean);
6492 -- Following checks are only for source types
6494 if Comes_From_Source (N) then
6495 if not Scalar_Part_Present (P_Type) then
6496 Error_Attr_P
6497 ("??attribute % always True, no scalars to check");
6498 end if;
6500 -- Not allowed for unchecked union type
6502 if Has_Unchecked_Union (P_Type) then
6503 Error_Attr_P
6504 ("attribute % not allowed for Unchecked_Union type");
6505 end if;
6506 end if;
6508 -----------
6509 -- Value --
6510 -----------
6512 when Attribute_Value => Value :
6513 begin
6514 Check_SPARK_05_Restriction_On_Attribute;
6515 Check_E1;
6516 Check_Scalar_Type;
6518 -- Case of enumeration type
6520 -- When an enumeration type appears in an attribute reference, all
6521 -- literals of the type are marked as referenced. This must only be
6522 -- done if the attribute reference appears in the current source.
6523 -- Otherwise the information on references may differ between a
6524 -- normal compilation and one that performs inlining.
6526 if Is_Enumeration_Type (P_Type)
6527 and then In_Extended_Main_Code_Unit (N)
6528 then
6529 Check_Restriction (No_Enumeration_Maps, N);
6531 -- Mark all enumeration literals as referenced, since the use of
6532 -- the Value attribute can implicitly reference any of the
6533 -- literals of the enumeration base type.
6535 declare
6536 Ent : Entity_Id := First_Literal (P_Base_Type);
6537 begin
6538 while Present (Ent) loop
6539 Set_Referenced (Ent);
6540 Next_Literal (Ent);
6541 end loop;
6542 end;
6543 end if;
6545 -- Set Etype before resolving expression because expansion of
6546 -- expression may require enclosing type. Note that the type
6547 -- returned by 'Value is the base type of the prefix type.
6549 Set_Etype (N, P_Base_Type);
6550 Validate_Non_Static_Attribute_Function_Call;
6552 -- Check restriction No_Fixed_IO
6554 if Restriction_Check_Required (No_Fixed_IO)
6555 and then Is_Fixed_Point_Type (P_Type)
6556 then
6557 Check_Restriction (No_Fixed_IO, P);
6558 end if;
6559 end Value;
6561 ----------------
6562 -- Value_Size --
6563 ----------------
6565 when Attribute_Value_Size =>
6566 Check_E0;
6567 Check_Type;
6568 Check_Not_Incomplete_Type;
6569 Set_Etype (N, Universal_Integer);
6571 -------------
6572 -- Version --
6573 -------------
6575 when Attribute_Version =>
6576 Check_E0;
6577 Check_Program_Unit;
6578 Set_Etype (N, RTE (RE_Version_String));
6580 ------------------
6581 -- Wchar_T_Size --
6582 ------------------
6584 when Attribute_Wchar_T_Size =>
6585 Standard_Attribute (Interfaces_Wchar_T_Size);
6587 ----------------
6588 -- Wide_Image --
6589 ----------------
6591 when Attribute_Wide_Image => Wide_Image :
6592 begin
6593 Check_SPARK_05_Restriction_On_Attribute;
6594 Check_Scalar_Type;
6595 Set_Etype (N, Standard_Wide_String);
6596 Check_E1;
6597 Resolve (E1, P_Base_Type);
6598 Validate_Non_Static_Attribute_Function_Call;
6600 -- Check restriction No_Fixed_IO
6602 if Restriction_Check_Required (No_Fixed_IO)
6603 and then Is_Fixed_Point_Type (P_Type)
6604 then
6605 Check_Restriction (No_Fixed_IO, P);
6606 end if;
6607 end Wide_Image;
6609 ---------------------
6610 -- Wide_Wide_Image --
6611 ---------------------
6613 when Attribute_Wide_Wide_Image => Wide_Wide_Image :
6614 begin
6615 Check_Scalar_Type;
6616 Set_Etype (N, Standard_Wide_Wide_String);
6617 Check_E1;
6618 Resolve (E1, P_Base_Type);
6619 Validate_Non_Static_Attribute_Function_Call;
6621 -- Check restriction No_Fixed_IO
6623 if Restriction_Check_Required (No_Fixed_IO)
6624 and then Is_Fixed_Point_Type (P_Type)
6625 then
6626 Check_Restriction (No_Fixed_IO, P);
6627 end if;
6628 end Wide_Wide_Image;
6630 ----------------
6631 -- Wide_Value --
6632 ----------------
6634 when Attribute_Wide_Value => Wide_Value :
6635 begin
6636 Check_SPARK_05_Restriction_On_Attribute;
6637 Check_E1;
6638 Check_Scalar_Type;
6640 -- Set Etype before resolving expression because expansion
6641 -- of expression may require enclosing type.
6643 Set_Etype (N, P_Type);
6644 Validate_Non_Static_Attribute_Function_Call;
6646 -- Check restriction No_Fixed_IO
6648 if Restriction_Check_Required (No_Fixed_IO)
6649 and then Is_Fixed_Point_Type (P_Type)
6650 then
6651 Check_Restriction (No_Fixed_IO, P);
6652 end if;
6653 end Wide_Value;
6655 ---------------------
6656 -- Wide_Wide_Value --
6657 ---------------------
6659 when Attribute_Wide_Wide_Value => Wide_Wide_Value :
6660 begin
6661 Check_E1;
6662 Check_Scalar_Type;
6664 -- Set Etype before resolving expression because expansion
6665 -- of expression may require enclosing type.
6667 Set_Etype (N, P_Type);
6668 Validate_Non_Static_Attribute_Function_Call;
6670 -- Check restriction No_Fixed_IO
6672 if Restriction_Check_Required (No_Fixed_IO)
6673 and then Is_Fixed_Point_Type (P_Type)
6674 then
6675 Check_Restriction (No_Fixed_IO, P);
6676 end if;
6677 end Wide_Wide_Value;
6679 ---------------------
6680 -- Wide_Wide_Width --
6681 ---------------------
6683 when Attribute_Wide_Wide_Width =>
6684 Check_E0;
6685 Check_Scalar_Type;
6686 Set_Etype (N, Universal_Integer);
6688 ----------------
6689 -- Wide_Width --
6690 ----------------
6692 when Attribute_Wide_Width =>
6693 Check_SPARK_05_Restriction_On_Attribute;
6694 Check_E0;
6695 Check_Scalar_Type;
6696 Set_Etype (N, Universal_Integer);
6698 -----------
6699 -- Width --
6700 -----------
6702 when Attribute_Width =>
6703 Check_SPARK_05_Restriction_On_Attribute;
6704 Check_E0;
6705 Check_Scalar_Type;
6706 Set_Etype (N, Universal_Integer);
6708 ---------------
6709 -- Word_Size --
6710 ---------------
6712 when Attribute_Word_Size =>
6713 Standard_Attribute (System_Word_Size);
6715 -----------
6716 -- Write --
6717 -----------
6719 when Attribute_Write =>
6720 Check_E2;
6721 Check_Stream_Attribute (TSS_Stream_Write);
6722 Set_Etype (N, Standard_Void_Type);
6723 Resolve (N, Standard_Void_Type);
6725 end case;
6727 -- All errors raise Bad_Attribute, so that we get out before any further
6728 -- damage occurs when an error is detected (for example, if we check for
6729 -- one attribute expression, and the check succeeds, we want to be able
6730 -- to proceed securely assuming that an expression is in fact present.
6732 -- Note: we set the attribute analyzed in this case to prevent any
6733 -- attempt at reanalysis which could generate spurious error msgs.
6735 exception
6736 when Bad_Attribute =>
6737 Set_Analyzed (N);
6738 Set_Etype (N, Any_Type);
6739 return;
6740 end Analyze_Attribute;
6742 --------------------
6743 -- Eval_Attribute --
6744 --------------------
6746 procedure Eval_Attribute (N : Node_Id) is
6747 Loc : constant Source_Ptr := Sloc (N);
6748 Aname : constant Name_Id := Attribute_Name (N);
6749 Id : constant Attribute_Id := Get_Attribute_Id (Aname);
6750 P : constant Node_Id := Prefix (N);
6752 C_Type : constant Entity_Id := Etype (N);
6753 -- The type imposed by the context
6755 E1 : Node_Id;
6756 -- First expression, or Empty if none
6758 E2 : Node_Id;
6759 -- Second expression, or Empty if none
6761 P_Entity : Entity_Id;
6762 -- Entity denoted by prefix
6764 P_Type : Entity_Id;
6765 -- The type of the prefix
6767 P_Base_Type : Entity_Id;
6768 -- The base type of the prefix type
6770 P_Root_Type : Entity_Id;
6771 -- The root type of the prefix type
6773 Static : Boolean;
6774 -- True if the result is Static. This is set by the general processing
6775 -- to true if the prefix is static, and all expressions are static. It
6776 -- can be reset as processing continues for particular attributes. This
6777 -- flag can still be True if the reference raises a constraint error.
6778 -- Is_Static_Expression (N) is set to follow this value as it is set
6779 -- and we could always reference this, but it is convenient to have a
6780 -- simple short name to use, since it is frequently referenced.
6782 Lo_Bound, Hi_Bound : Node_Id;
6783 -- Expressions for low and high bounds of type or array index referenced
6784 -- by First, Last, or Length attribute for array, set by Set_Bounds.
6786 CE_Node : Node_Id;
6787 -- Constraint error node used if we have an attribute reference has
6788 -- an argument that raises a constraint error. In this case we replace
6789 -- the attribute with a raise constraint_error node. This is important
6790 -- processing, since otherwise gigi might see an attribute which it is
6791 -- unprepared to deal with.
6793 procedure Check_Concurrent_Discriminant (Bound : Node_Id);
6794 -- If Bound is a reference to a discriminant of a task or protected type
6795 -- occurring within the object's body, rewrite attribute reference into
6796 -- a reference to the corresponding discriminal. Use for the expansion
6797 -- of checks against bounds of entry family index subtypes.
6799 procedure Check_Expressions;
6800 -- In case where the attribute is not foldable, the expressions, if
6801 -- any, of the attribute, are in a non-static context. This procedure
6802 -- performs the required additional checks.
6804 function Compile_Time_Known_Bounds (Typ : Entity_Id) return Boolean;
6805 -- Determines if the given type has compile time known bounds. Note
6806 -- that we enter the case statement even in cases where the prefix
6807 -- type does NOT have known bounds, so it is important to guard any
6808 -- attempt to evaluate both bounds with a call to this function.
6810 procedure Compile_Time_Known_Attribute (N : Node_Id; Val : Uint);
6811 -- This procedure is called when the attribute N has a non-static
6812 -- but compile time known value given by Val. It includes the
6813 -- necessary checks for out of range values.
6815 function Fore_Value return Nat;
6816 -- Computes the Fore value for the current attribute prefix, which is
6817 -- known to be a static fixed-point type. Used by Fore and Width.
6819 function Mantissa return Uint;
6820 -- Returns the Mantissa value for the prefix type
6822 procedure Set_Bounds;
6823 -- Used for First, Last and Length attributes applied to an array or
6824 -- array subtype. Sets the variables Lo_Bound and Hi_Bound to the low
6825 -- and high bound expressions for the index referenced by the attribute
6826 -- designator (i.e. the first index if no expression is present, and the
6827 -- N'th index if the value N is present as an expression). Also used for
6828 -- First and Last of scalar types and for First_Valid and Last_Valid.
6829 -- Static is reset to False if the type or index type is not statically
6830 -- constrained.
6832 function Statically_Denotes_Entity (N : Node_Id) return Boolean;
6833 -- Verify that the prefix of a potentially static array attribute
6834 -- satisfies the conditions of 4.9 (14).
6836 -----------------------------------
6837 -- Check_Concurrent_Discriminant --
6838 -----------------------------------
6840 procedure Check_Concurrent_Discriminant (Bound : Node_Id) is
6841 Tsk : Entity_Id;
6842 -- The concurrent (task or protected) type
6844 begin
6845 if Nkind (Bound) = N_Identifier
6846 and then Ekind (Entity (Bound)) = E_Discriminant
6847 and then Is_Concurrent_Record_Type (Scope (Entity (Bound)))
6848 then
6849 Tsk := Corresponding_Concurrent_Type (Scope (Entity (Bound)));
6851 if In_Open_Scopes (Tsk) and then Has_Completion (Tsk) then
6853 -- Find discriminant of original concurrent type, and use
6854 -- its current discriminal, which is the renaming within
6855 -- the task/protected body.
6857 Rewrite (N,
6858 New_Occurrence_Of
6859 (Find_Body_Discriminal (Entity (Bound)), Loc));
6860 end if;
6861 end if;
6862 end Check_Concurrent_Discriminant;
6864 -----------------------
6865 -- Check_Expressions --
6866 -----------------------
6868 procedure Check_Expressions is
6869 E : Node_Id;
6870 begin
6871 E := E1;
6872 while Present (E) loop
6873 Check_Non_Static_Context (E);
6874 Next (E);
6875 end loop;
6876 end Check_Expressions;
6878 ----------------------------------
6879 -- Compile_Time_Known_Attribute --
6880 ----------------------------------
6882 procedure Compile_Time_Known_Attribute (N : Node_Id; Val : Uint) is
6883 T : constant Entity_Id := Etype (N);
6885 begin
6886 Fold_Uint (N, Val, False);
6888 -- Check that result is in bounds of the type if it is static
6890 if Is_In_Range (N, T, Assume_Valid => False) then
6891 null;
6893 elsif Is_Out_Of_Range (N, T) then
6894 Apply_Compile_Time_Constraint_Error
6895 (N, "value not in range of}??", CE_Range_Check_Failed);
6897 elsif not Range_Checks_Suppressed (T) then
6898 Enable_Range_Check (N);
6900 else
6901 Set_Do_Range_Check (N, False);
6902 end if;
6903 end Compile_Time_Known_Attribute;
6905 -------------------------------
6906 -- Compile_Time_Known_Bounds --
6907 -------------------------------
6909 function Compile_Time_Known_Bounds (Typ : Entity_Id) return Boolean is
6910 begin
6911 return
6912 Compile_Time_Known_Value (Type_Low_Bound (Typ))
6913 and then
6914 Compile_Time_Known_Value (Type_High_Bound (Typ));
6915 end Compile_Time_Known_Bounds;
6917 ----------------
6918 -- Fore_Value --
6919 ----------------
6921 -- Note that the Fore calculation is based on the actual values
6922 -- of the bounds, and does not take into account possible rounding.
6924 function Fore_Value return Nat is
6925 Lo : constant Uint := Expr_Value (Type_Low_Bound (P_Type));
6926 Hi : constant Uint := Expr_Value (Type_High_Bound (P_Type));
6927 Small : constant Ureal := Small_Value (P_Type);
6928 Lo_Real : constant Ureal := Lo * Small;
6929 Hi_Real : constant Ureal := Hi * Small;
6930 T : Ureal;
6931 R : Nat;
6933 begin
6934 -- Bounds are given in terms of small units, so first compute
6935 -- proper values as reals.
6937 T := UR_Max (abs Lo_Real, abs Hi_Real);
6938 R := 2;
6940 -- Loop to compute proper value if more than one digit required
6942 while T >= Ureal_10 loop
6943 R := R + 1;
6944 T := T / Ureal_10;
6945 end loop;
6947 return R;
6948 end Fore_Value;
6950 --------------
6951 -- Mantissa --
6952 --------------
6954 -- Table of mantissa values accessed by function Computed using
6955 -- the relation:
6957 -- T'Mantissa = integer next above (D * log(10)/log(2)) + 1)
6959 -- where D is T'Digits (RM83 3.5.7)
6961 Mantissa_Value : constant array (Nat range 1 .. 40) of Nat := (
6962 1 => 5,
6963 2 => 8,
6964 3 => 11,
6965 4 => 15,
6966 5 => 18,
6967 6 => 21,
6968 7 => 25,
6969 8 => 28,
6970 9 => 31,
6971 10 => 35,
6972 11 => 38,
6973 12 => 41,
6974 13 => 45,
6975 14 => 48,
6976 15 => 51,
6977 16 => 55,
6978 17 => 58,
6979 18 => 61,
6980 19 => 65,
6981 20 => 68,
6982 21 => 71,
6983 22 => 75,
6984 23 => 78,
6985 24 => 81,
6986 25 => 85,
6987 26 => 88,
6988 27 => 91,
6989 28 => 95,
6990 29 => 98,
6991 30 => 101,
6992 31 => 104,
6993 32 => 108,
6994 33 => 111,
6995 34 => 114,
6996 35 => 118,
6997 36 => 121,
6998 37 => 124,
6999 38 => 128,
7000 39 => 131,
7001 40 => 134);
7003 function Mantissa return Uint is
7004 begin
7005 return
7006 UI_From_Int (Mantissa_Value (UI_To_Int (Digits_Value (P_Type))));
7007 end Mantissa;
7009 ----------------
7010 -- Set_Bounds --
7011 ----------------
7013 procedure Set_Bounds is
7014 Ndim : Nat;
7015 Indx : Node_Id;
7016 Ityp : Entity_Id;
7018 begin
7019 -- For a string literal subtype, we have to construct the bounds.
7020 -- Valid Ada code never applies attributes to string literals, but
7021 -- it is convenient to allow the expander to generate attribute
7022 -- references of this type (e.g. First and Last applied to a string
7023 -- literal).
7025 -- Note that the whole point of the E_String_Literal_Subtype is to
7026 -- avoid this construction of bounds, but the cases in which we
7027 -- have to materialize them are rare enough that we don't worry.
7029 -- The low bound is simply the low bound of the base type. The
7030 -- high bound is computed from the length of the string and this
7031 -- low bound.
7033 if Ekind (P_Type) = E_String_Literal_Subtype then
7034 Ityp := Etype (First_Index (Base_Type (P_Type)));
7035 Lo_Bound := Type_Low_Bound (Ityp);
7037 Hi_Bound :=
7038 Make_Integer_Literal (Sloc (P),
7039 Intval =>
7040 Expr_Value (Lo_Bound) + String_Literal_Length (P_Type) - 1);
7042 Set_Parent (Hi_Bound, P);
7043 Analyze_And_Resolve (Hi_Bound, Etype (Lo_Bound));
7044 return;
7046 -- For non-array case, just get bounds of scalar type
7048 elsif Is_Scalar_Type (P_Type) then
7049 Ityp := P_Type;
7051 -- For a fixed-point type, we must freeze to get the attributes
7052 -- of the fixed-point type set now so we can reference them.
7054 if Is_Fixed_Point_Type (P_Type)
7055 and then not Is_Frozen (Base_Type (P_Type))
7056 and then Compile_Time_Known_Value (Type_Low_Bound (P_Type))
7057 and then Compile_Time_Known_Value (Type_High_Bound (P_Type))
7058 then
7059 Freeze_Fixed_Point_Type (Base_Type (P_Type));
7060 end if;
7062 -- For array case, get type of proper index
7064 else
7065 if No (E1) then
7066 Ndim := 1;
7067 else
7068 Ndim := UI_To_Int (Expr_Value (E1));
7069 end if;
7071 Indx := First_Index (P_Type);
7072 for J in 1 .. Ndim - 1 loop
7073 Next_Index (Indx);
7074 end loop;
7076 -- If no index type, get out (some other error occurred, and
7077 -- we don't have enough information to complete the job).
7079 if No (Indx) then
7080 Lo_Bound := Error;
7081 Hi_Bound := Error;
7082 return;
7083 end if;
7085 Ityp := Etype (Indx);
7086 end if;
7088 -- A discrete range in an index constraint is allowed to be a
7089 -- subtype indication. This is syntactically a pain, but should
7090 -- not propagate to the entity for the corresponding index subtype.
7091 -- After checking that the subtype indication is legal, the range
7092 -- of the subtype indication should be transfered to the entity.
7093 -- The attributes for the bounds should remain the simple retrievals
7094 -- that they are now.
7096 Lo_Bound := Type_Low_Bound (Ityp);
7097 Hi_Bound := Type_High_Bound (Ityp);
7099 -- If subtype is non-static, result is definitely non-static
7101 if not Is_Static_Subtype (Ityp) then
7102 Static := False;
7103 Set_Is_Static_Expression (N, False);
7105 -- Subtype is static, does it raise CE?
7107 elsif not Is_OK_Static_Subtype (Ityp) then
7108 Set_Raises_Constraint_Error (N);
7109 end if;
7110 end Set_Bounds;
7112 -------------------------------
7113 -- Statically_Denotes_Entity --
7114 -------------------------------
7116 function Statically_Denotes_Entity (N : Node_Id) return Boolean is
7117 E : Entity_Id;
7119 begin
7120 if not Is_Entity_Name (N) then
7121 return False;
7122 else
7123 E := Entity (N);
7124 end if;
7126 return
7127 Nkind (Parent (E)) /= N_Object_Renaming_Declaration
7128 or else Statically_Denotes_Entity (Renamed_Object (E));
7129 end Statically_Denotes_Entity;
7131 -- Start of processing for Eval_Attribute
7133 begin
7134 -- Initialize result as non-static, will be reset if appropriate
7136 Set_Is_Static_Expression (N, False);
7137 Static := False;
7139 -- Acquire first two expressions (at the moment, no attributes take more
7140 -- than two expressions in any case).
7142 if Present (Expressions (N)) then
7143 E1 := First (Expressions (N));
7144 E2 := Next (E1);
7145 else
7146 E1 := Empty;
7147 E2 := Empty;
7148 end if;
7150 -- Special processing for Enabled attribute. This attribute has a very
7151 -- special prefix, and the easiest way to avoid lots of special checks
7152 -- to protect this special prefix from causing trouble is to deal with
7153 -- this attribute immediately and be done with it.
7155 if Id = Attribute_Enabled then
7157 -- We skip evaluation if the expander is not active. This is not just
7158 -- an optimization. It is of key importance that we not rewrite the
7159 -- attribute in a generic template, since we want to pick up the
7160 -- setting of the check in the instance, and testing expander active
7161 -- is as easy way of doing this as any.
7163 if Expander_Active then
7164 declare
7165 C : constant Check_Id := Get_Check_Id (Chars (P));
7166 R : Boolean;
7168 begin
7169 if No (E1) then
7170 if C in Predefined_Check_Id then
7171 R := Scope_Suppress.Suppress (C);
7172 else
7173 R := Is_Check_Suppressed (Empty, C);
7174 end if;
7176 else
7177 R := Is_Check_Suppressed (Entity (E1), C);
7178 end if;
7180 Rewrite (N, New_Occurrence_Of (Boolean_Literals (not R), Loc));
7181 end;
7182 end if;
7184 return;
7185 end if;
7187 -- Special processing for cases where the prefix is an object. For
7188 -- this purpose, a string literal counts as an object (attributes
7189 -- of string literals can only appear in generated code).
7191 if Is_Object_Reference (P) or else Nkind (P) = N_String_Literal then
7193 -- For Component_Size, the prefix is an array object, and we apply
7194 -- the attribute to the type of the object. This is allowed for
7195 -- both unconstrained and constrained arrays, since the bounds
7196 -- have no influence on the value of this attribute.
7198 if Id = Attribute_Component_Size then
7199 P_Entity := Etype (P);
7201 -- For First and Last, the prefix is an array object, and we apply
7202 -- the attribute to the type of the array, but we need a constrained
7203 -- type for this, so we use the actual subtype if available.
7205 elsif Id = Attribute_First or else
7206 Id = Attribute_Last or else
7207 Id = Attribute_Length
7208 then
7209 declare
7210 AS : constant Entity_Id := Get_Actual_Subtype_If_Available (P);
7212 begin
7213 if Present (AS) and then Is_Constrained (AS) then
7214 P_Entity := AS;
7216 -- If we have an unconstrained type we cannot fold
7218 else
7219 Check_Expressions;
7220 return;
7221 end if;
7222 end;
7224 -- For Size, give size of object if available, otherwise we
7225 -- cannot fold Size.
7227 elsif Id = Attribute_Size then
7228 if Is_Entity_Name (P)
7229 and then Known_Esize (Entity (P))
7230 then
7231 Compile_Time_Known_Attribute (N, Esize (Entity (P)));
7232 return;
7234 else
7235 Check_Expressions;
7236 return;
7237 end if;
7239 -- For Alignment, give size of object if available, otherwise we
7240 -- cannot fold Alignment.
7242 elsif Id = Attribute_Alignment then
7243 if Is_Entity_Name (P)
7244 and then Known_Alignment (Entity (P))
7245 then
7246 Fold_Uint (N, Alignment (Entity (P)), Static);
7247 return;
7249 else
7250 Check_Expressions;
7251 return;
7252 end if;
7254 -- For Lock_Free, we apply the attribute to the type of the object.
7255 -- This is allowed since we have already verified that the type is a
7256 -- protected type.
7258 elsif Id = Attribute_Lock_Free then
7259 P_Entity := Etype (P);
7261 -- No other attributes for objects are folded
7263 else
7264 Check_Expressions;
7265 return;
7266 end if;
7268 -- Cases where P is not an object. Cannot do anything if P is not the
7269 -- name of an entity.
7271 elsif not Is_Entity_Name (P) then
7272 Check_Expressions;
7273 return;
7275 -- Otherwise get prefix entity
7277 else
7278 P_Entity := Entity (P);
7279 end if;
7281 -- If we are asked to evaluate an attribute where the prefix is a
7282 -- non-frozen generic actual type whose RM_Size is still set to zero,
7283 -- then abandon the effort.
7285 if Is_Type (P_Entity)
7286 and then (not Is_Frozen (P_Entity)
7287 and then Is_Generic_Actual_Type (P_Entity)
7288 and then RM_Size (P_Entity) = 0)
7290 -- However, the attribute Unconstrained_Array must be evaluated,
7291 -- since it is documented to be a static attribute (and can for
7292 -- example appear in a Compile_Time_Warning pragma). The frozen
7293 -- status of the type does not affect its evaluation.
7295 and then Id /= Attribute_Unconstrained_Array
7296 then
7297 return;
7298 end if;
7300 -- At this stage P_Entity is the entity to which the attribute
7301 -- is to be applied. This is usually simply the entity of the
7302 -- prefix, except in some cases of attributes for objects, where
7303 -- as described above, we apply the attribute to the object type.
7305 -- Here is where we make sure that static attributes are properly
7306 -- marked as such. These are attributes whose prefix is a static
7307 -- scalar subtype, whose result is scalar, and whose arguments, if
7308 -- present, are static scalar expressions. Note that such references
7309 -- are static expressions even if they raise Constraint_Error.
7311 -- For example, Boolean'Pos (1/0 = 0) is a static expression, even
7312 -- though evaluating it raises constraint error. This means that a
7313 -- declaration like:
7315 -- X : constant := (if True then 1 else Boolean'Pos (1/0 = 0));
7317 -- is legal, since here this expression appears in a statically
7318 -- unevaluated position, so it does not actually raise an exception.
7320 if Is_Scalar_Type (P_Entity)
7321 and then (not Is_Generic_Type (P_Entity))
7322 and then Is_Static_Subtype (P_Entity)
7323 and then Is_Scalar_Type (Etype (N))
7324 and then
7325 (No (E1)
7326 or else (Is_Static_Expression (E1)
7327 and then Is_Scalar_Type (Etype (E1))))
7328 and then
7329 (No (E2)
7330 or else (Is_Static_Expression (E2)
7331 and then Is_Scalar_Type (Etype (E1))))
7332 then
7333 Static := True;
7334 Set_Is_Static_Expression (N, True);
7335 end if;
7337 -- First foldable possibility is a scalar or array type (RM 4.9(7))
7338 -- that is not generic (generic types are eliminated by RM 4.9(25)).
7339 -- Note we allow non-static non-generic types at this stage as further
7340 -- described below.
7342 if Is_Type (P_Entity)
7343 and then (Is_Scalar_Type (P_Entity) or Is_Array_Type (P_Entity))
7344 and then (not Is_Generic_Type (P_Entity))
7345 then
7346 P_Type := P_Entity;
7348 -- Second foldable possibility is an array object (RM 4.9(8))
7350 elsif (Ekind (P_Entity) = E_Variable
7351 or else
7352 Ekind (P_Entity) = E_Constant)
7353 and then Is_Array_Type (Etype (P_Entity))
7354 and then (not Is_Generic_Type (Etype (P_Entity)))
7355 then
7356 P_Type := Etype (P_Entity);
7358 -- If the entity is an array constant with an unconstrained nominal
7359 -- subtype then get the type from the initial value. If the value has
7360 -- been expanded into assignments, there is no expression and the
7361 -- attribute reference remains dynamic.
7363 -- We could do better here and retrieve the type ???
7365 if Ekind (P_Entity) = E_Constant
7366 and then not Is_Constrained (P_Type)
7367 then
7368 if No (Constant_Value (P_Entity)) then
7369 return;
7370 else
7371 P_Type := Etype (Constant_Value (P_Entity));
7372 end if;
7373 end if;
7375 -- Definite must be folded if the prefix is not a generic type, that
7376 -- is to say if we are within an instantiation. Same processing applies
7377 -- to the GNAT attributes Atomic_Always_Lock_Free, Has_Discriminants,
7378 -- Lock_Free, Type_Class, Has_Tagged_Value, and Unconstrained_Array.
7380 elsif (Id = Attribute_Atomic_Always_Lock_Free or else
7381 Id = Attribute_Definite or else
7382 Id = Attribute_Has_Access_Values or else
7383 Id = Attribute_Has_Discriminants or else
7384 Id = Attribute_Has_Tagged_Values or else
7385 Id = Attribute_Lock_Free or else
7386 Id = Attribute_Type_Class or else
7387 Id = Attribute_Unconstrained_Array or else
7388 Id = Attribute_Max_Alignment_For_Allocation)
7389 and then not Is_Generic_Type (P_Entity)
7390 then
7391 P_Type := P_Entity;
7393 -- We can fold 'Size applied to a type if the size is known (as happens
7394 -- for a size from an attribute definition clause). At this stage, this
7395 -- can happen only for types (e.g. record types) for which the size is
7396 -- always non-static. We exclude generic types from consideration (since
7397 -- they have bogus sizes set within templates).
7399 elsif Id = Attribute_Size
7400 and then Is_Type (P_Entity)
7401 and then (not Is_Generic_Type (P_Entity))
7402 and then Known_Static_RM_Size (P_Entity)
7403 then
7404 Compile_Time_Known_Attribute (N, RM_Size (P_Entity));
7405 return;
7407 -- We can fold 'Alignment applied to a type if the alignment is known
7408 -- (as happens for an alignment from an attribute definition clause).
7409 -- At this stage, this can happen only for types (e.g. record types) for
7410 -- which the size is always non-static. We exclude generic types from
7411 -- consideration (since they have bogus sizes set within templates).
7413 elsif Id = Attribute_Alignment
7414 and then Is_Type (P_Entity)
7415 and then (not Is_Generic_Type (P_Entity))
7416 and then Known_Alignment (P_Entity)
7417 then
7418 Compile_Time_Known_Attribute (N, Alignment (P_Entity));
7419 return;
7421 -- If this is an access attribute that is known to fail accessibility
7422 -- check, rewrite accordingly.
7424 elsif Attribute_Name (N) = Name_Access
7425 and then Raises_Constraint_Error (N)
7426 then
7427 Rewrite (N,
7428 Make_Raise_Program_Error (Loc,
7429 Reason => PE_Accessibility_Check_Failed));
7430 Set_Etype (N, C_Type);
7431 return;
7433 -- No other cases are foldable (they certainly aren't static, and at
7434 -- the moment we don't try to fold any cases other than the ones above).
7436 else
7437 Check_Expressions;
7438 return;
7439 end if;
7441 -- If either attribute or the prefix is Any_Type, then propagate
7442 -- Any_Type to the result and don't do anything else at all.
7444 if P_Type = Any_Type
7445 or else (Present (E1) and then Etype (E1) = Any_Type)
7446 or else (Present (E2) and then Etype (E2) = Any_Type)
7447 then
7448 Set_Etype (N, Any_Type);
7449 return;
7450 end if;
7452 -- Scalar subtype case. We have not yet enforced the static requirement
7453 -- of (RM 4.9(7)) and we don't intend to just yet, since there are cases
7454 -- of non-static attribute references (e.g. S'Digits for a non-static
7455 -- floating-point type, which we can compute at compile time).
7457 -- Note: this folding of non-static attributes is not simply a case of
7458 -- optimization. For many of the attributes affected, Gigi cannot handle
7459 -- the attribute and depends on the front end having folded them away.
7461 -- Note: although we don't require staticness at this stage, we do set
7462 -- the Static variable to record the staticness, for easy reference by
7463 -- those attributes where it matters (e.g. Succ and Pred), and also to
7464 -- be used to ensure that non-static folded things are not marked as
7465 -- being static (a check that is done right at the end).
7467 P_Root_Type := Root_Type (P_Type);
7468 P_Base_Type := Base_Type (P_Type);
7470 -- If the root type or base type is generic, then we cannot fold. This
7471 -- test is needed because subtypes of generic types are not always
7472 -- marked as being generic themselves (which seems odd???)
7474 if Is_Generic_Type (P_Root_Type)
7475 or else Is_Generic_Type (P_Base_Type)
7476 then
7477 return;
7478 end if;
7480 if Is_Scalar_Type (P_Type) then
7481 if not Is_Static_Subtype (P_Type) then
7482 Static := False;
7483 Set_Is_Static_Expression (N, False);
7484 elsif not Is_OK_Static_Subtype (P_Type) then
7485 Set_Raises_Constraint_Error (N);
7486 end if;
7488 -- Array case. We enforce the constrained requirement of (RM 4.9(7-8))
7489 -- since we can't do anything with unconstrained arrays. In addition,
7490 -- only the First, Last and Length attributes are possibly static.
7492 -- Atomic_Always_Lock_Free, Definite, Has_Access_Values,
7493 -- Has_Discriminants, Has_Tagged_Values, Lock_Free, Type_Class, and
7494 -- Unconstrained_Array are again exceptions, because they apply as well
7495 -- to unconstrained types.
7497 -- In addition Component_Size is an exception since it is possibly
7498 -- foldable, even though it is never static, and it does apply to
7499 -- unconstrained arrays. Furthermore, it is essential to fold this
7500 -- in the packed case, since otherwise the value will be incorrect.
7502 elsif Id = Attribute_Atomic_Always_Lock_Free or else
7503 Id = Attribute_Definite or else
7504 Id = Attribute_Has_Access_Values or else
7505 Id = Attribute_Has_Discriminants or else
7506 Id = Attribute_Has_Tagged_Values or else
7507 Id = Attribute_Lock_Free or else
7508 Id = Attribute_Type_Class or else
7509 Id = Attribute_Unconstrained_Array or else
7510 Id = Attribute_Component_Size
7511 then
7512 Static := False;
7513 Set_Is_Static_Expression (N, False);
7515 elsif Id /= Attribute_Max_Alignment_For_Allocation then
7516 if not Is_Constrained (P_Type)
7517 or else (Id /= Attribute_First and then
7518 Id /= Attribute_Last and then
7519 Id /= Attribute_Length)
7520 then
7521 Check_Expressions;
7522 return;
7523 end if;
7525 -- The rules in (RM 4.9(7,8)) require a static array, but as in the
7526 -- scalar case, we hold off on enforcing staticness, since there are
7527 -- cases which we can fold at compile time even though they are not
7528 -- static (e.g. 'Length applied to a static index, even though other
7529 -- non-static indexes make the array type non-static). This is only
7530 -- an optimization, but it falls out essentially free, so why not.
7531 -- Again we compute the variable Static for easy reference later
7532 -- (note that no array attributes are static in Ada 83).
7534 -- We also need to set Static properly for subsequent legality checks
7535 -- which might otherwise accept non-static constants in contexts
7536 -- where they are not legal.
7538 Static :=
7539 Ada_Version >= Ada_95 and then Statically_Denotes_Entity (P);
7540 Set_Is_Static_Expression (N, Static);
7542 declare
7543 Nod : Node_Id;
7545 begin
7546 Nod := First_Index (P_Type);
7548 -- The expression is static if the array type is constrained
7549 -- by given bounds, and not by an initial expression. Constant
7550 -- strings are static in any case.
7552 if Root_Type (P_Type) /= Standard_String then
7553 Static :=
7554 Static and then not Is_Constr_Subt_For_U_Nominal (P_Type);
7555 Set_Is_Static_Expression (N, Static);
7557 end if;
7559 while Present (Nod) loop
7560 if not Is_Static_Subtype (Etype (Nod)) then
7561 Static := False;
7562 Set_Is_Static_Expression (N, False);
7563 elsif not Is_OK_Static_Subtype (Etype (Nod)) then
7564 Set_Raises_Constraint_Error (N);
7565 end if;
7567 -- If however the index type is generic, or derived from
7568 -- one, attributes cannot be folded.
7570 if Is_Generic_Type (Root_Type (Etype (Nod)))
7571 and then Id /= Attribute_Component_Size
7572 then
7573 return;
7574 end if;
7576 Next_Index (Nod);
7577 end loop;
7578 end;
7579 end if;
7581 -- Check any expressions that are present. Note that these expressions,
7582 -- depending on the particular attribute type, are either part of the
7583 -- attribute designator, or they are arguments in a case where the
7584 -- attribute reference returns a function. In the latter case, the
7585 -- rule in (RM 4.9(22)) applies and in particular requires the type
7586 -- of the expressions to be scalar in order for the attribute to be
7587 -- considered to be static.
7589 declare
7590 E : Node_Id;
7592 begin
7593 E := E1;
7594 while Present (E) loop
7596 -- If expression is not static, then the attribute reference
7597 -- result certainly cannot be static.
7599 if not Is_Static_Expression (E) then
7600 Static := False;
7601 Set_Is_Static_Expression (N, False);
7602 end if;
7604 if Raises_Constraint_Error (E) then
7605 Set_Raises_Constraint_Error (N);
7606 end if;
7608 -- If the result is not known at compile time, or is not of
7609 -- a scalar type, then the result is definitely not static,
7610 -- so we can quit now.
7612 if not Compile_Time_Known_Value (E)
7613 or else not Is_Scalar_Type (Etype (E))
7614 then
7615 -- An odd special case, if this is a Pos attribute, this
7616 -- is where we need to apply a range check since it does
7617 -- not get done anywhere else.
7619 if Id = Attribute_Pos then
7620 if Is_Integer_Type (Etype (E)) then
7621 Apply_Range_Check (E, Etype (N));
7622 end if;
7623 end if;
7625 Check_Expressions;
7626 return;
7628 -- If the expression raises a constraint error, then so does
7629 -- the attribute reference. We keep going in this case because
7630 -- we are still interested in whether the attribute reference
7631 -- is static even if it is not static.
7633 elsif Raises_Constraint_Error (E) then
7634 Set_Raises_Constraint_Error (N);
7635 end if;
7637 Next (E);
7638 end loop;
7640 if Raises_Constraint_Error (Prefix (N)) then
7641 return;
7642 end if;
7643 end;
7645 -- Deal with the case of a static attribute reference that raises
7646 -- constraint error. The Raises_Constraint_Error flag will already
7647 -- have been set, and the Static flag shows whether the attribute
7648 -- reference is static. In any case we certainly can't fold such an
7649 -- attribute reference.
7651 -- Note that the rewriting of the attribute node with the constraint
7652 -- error node is essential in this case, because otherwise Gigi might
7653 -- blow up on one of the attributes it never expects to see.
7655 -- The constraint_error node must have the type imposed by the context,
7656 -- to avoid spurious errors in the enclosing expression.
7658 if Raises_Constraint_Error (N) then
7659 CE_Node :=
7660 Make_Raise_Constraint_Error (Sloc (N),
7661 Reason => CE_Range_Check_Failed);
7662 Set_Etype (CE_Node, Etype (N));
7663 Set_Raises_Constraint_Error (CE_Node);
7664 Check_Expressions;
7665 Rewrite (N, Relocate_Node (CE_Node));
7666 Set_Raises_Constraint_Error (N, True);
7667 return;
7668 end if;
7670 -- At this point we have a potentially foldable attribute reference.
7671 -- If Static is set, then the attribute reference definitely obeys
7672 -- the requirements in (RM 4.9(7,8,22)), and it definitely can be
7673 -- folded. If Static is not set, then the attribute may or may not
7674 -- be foldable, and the individual attribute processing routines
7675 -- test Static as required in cases where it makes a difference.
7677 -- In the case where Static is not set, we do know that all the
7678 -- expressions present are at least known at compile time (we assumed
7679 -- above that if this was not the case, then there was no hope of static
7680 -- evaluation). However, we did not require that the bounds of the
7681 -- prefix type be compile time known, let alone static). That's because
7682 -- there are many attributes that can be computed at compile time on
7683 -- non-static subtypes, even though such references are not static
7684 -- expressions.
7686 -- For VAX float, the root type is an IEEE type. So make sure to use the
7687 -- base type instead of the root-type for floating point attributes.
7689 case Id is
7691 -- Attributes related to Ada 2012 iterators (placeholder ???)
7693 when Attribute_Constant_Indexing |
7694 Attribute_Default_Iterator |
7695 Attribute_Implicit_Dereference |
7696 Attribute_Iterator_Element |
7697 Attribute_Iterable |
7698 Attribute_Variable_Indexing => null;
7700 -- Internal attributes used to deal with Ada 2012 delayed aspects.
7701 -- These were already rejected by the parser. Thus they shouldn't
7702 -- appear here.
7704 when Internal_Attribute_Id =>
7705 raise Program_Error;
7707 --------------
7708 -- Adjacent --
7709 --------------
7711 when Attribute_Adjacent =>
7712 Fold_Ureal
7714 Eval_Fat.Adjacent
7715 (P_Base_Type, Expr_Value_R (E1), Expr_Value_R (E2)),
7716 Static);
7718 ---------
7719 -- Aft --
7720 ---------
7722 when Attribute_Aft =>
7723 Fold_Uint (N, Aft_Value (P_Type), Static);
7725 ---------------
7726 -- Alignment --
7727 ---------------
7729 when Attribute_Alignment => Alignment_Block : declare
7730 P_TypeA : constant Entity_Id := Underlying_Type (P_Type);
7732 begin
7733 -- Fold if alignment is set and not otherwise
7735 if Known_Alignment (P_TypeA) then
7736 Fold_Uint (N, Alignment (P_TypeA), Static);
7737 end if;
7738 end Alignment_Block;
7740 -----------------------------
7741 -- Atomic_Always_Lock_Free --
7742 -----------------------------
7744 -- Atomic_Always_Lock_Free attribute is a Boolean, thus no need to fold
7745 -- here.
7747 when Attribute_Atomic_Always_Lock_Free => Atomic_Always_Lock_Free :
7748 declare
7749 V : constant Entity_Id :=
7750 Boolean_Literals
7751 (Support_Atomic_Primitives_On_Target
7752 and then Support_Atomic_Primitives (P_Type));
7754 begin
7755 Rewrite (N, New_Occurrence_Of (V, Loc));
7757 -- Analyze and resolve as boolean. Note that this attribute is a
7758 -- static attribute in GNAT.
7760 Analyze_And_Resolve (N, Standard_Boolean);
7761 Static := True;
7762 Set_Is_Static_Expression (N, True);
7763 end Atomic_Always_Lock_Free;
7765 ---------
7766 -- Bit --
7767 ---------
7769 -- Bit can never be folded
7771 when Attribute_Bit =>
7772 null;
7774 ------------------
7775 -- Body_Version --
7776 ------------------
7778 -- Body_version can never be static
7780 when Attribute_Body_Version =>
7781 null;
7783 -------------
7784 -- Ceiling --
7785 -------------
7787 when Attribute_Ceiling =>
7788 Fold_Ureal
7789 (N, Eval_Fat.Ceiling (P_Base_Type, Expr_Value_R (E1)), Static);
7791 --------------------
7792 -- Component_Size --
7793 --------------------
7795 when Attribute_Component_Size =>
7796 if Known_Static_Component_Size (P_Type) then
7797 Fold_Uint (N, Component_Size (P_Type), Static);
7798 end if;
7800 -------------
7801 -- Compose --
7802 -------------
7804 when Attribute_Compose =>
7805 Fold_Ureal
7807 Eval_Fat.Compose (P_Base_Type, Expr_Value_R (E1), Expr_Value (E2)),
7808 Static);
7810 -----------------
7811 -- Constrained --
7812 -----------------
7814 -- Constrained is never folded for now, there may be cases that
7815 -- could be handled at compile time. To be looked at later.
7817 when Attribute_Constrained =>
7819 -- The expander might fold it and set the static flag accordingly,
7820 -- but with expansion disabled (as in ASIS), it remains as an
7821 -- attribute reference, and this reference is not static.
7823 Set_Is_Static_Expression (N, False);
7824 null;
7826 ---------------
7827 -- Copy_Sign --
7828 ---------------
7830 when Attribute_Copy_Sign =>
7831 Fold_Ureal
7833 Eval_Fat.Copy_Sign
7834 (P_Base_Type, Expr_Value_R (E1), Expr_Value_R (E2)),
7835 Static);
7837 --------------
7838 -- Definite --
7839 --------------
7841 when Attribute_Definite =>
7842 Rewrite (N, New_Occurrence_Of (
7843 Boolean_Literals (not Is_Indefinite_Subtype (P_Entity)), Loc));
7844 Analyze_And_Resolve (N, Standard_Boolean);
7846 -----------
7847 -- Delta --
7848 -----------
7850 when Attribute_Delta =>
7851 Fold_Ureal (N, Delta_Value (P_Type), True);
7853 ------------
7854 -- Denorm --
7855 ------------
7857 when Attribute_Denorm =>
7858 Fold_Uint
7859 (N, UI_From_Int (Boolean'Pos (Has_Denormals (P_Type))), Static);
7861 ---------------------
7862 -- Descriptor_Size --
7863 ---------------------
7865 when Attribute_Descriptor_Size =>
7866 null;
7868 ------------
7869 -- Digits --
7870 ------------
7872 when Attribute_Digits =>
7873 Fold_Uint (N, Digits_Value (P_Type), Static);
7875 ----------
7876 -- Emax --
7877 ----------
7879 when Attribute_Emax =>
7881 -- Ada 83 attribute is defined as (RM83 3.5.8)
7883 -- T'Emax = 4 * T'Mantissa
7885 Fold_Uint (N, 4 * Mantissa, Static);
7887 --------------
7888 -- Enum_Rep --
7889 --------------
7891 when Attribute_Enum_Rep =>
7893 -- For an enumeration type with a non-standard representation use
7894 -- the Enumeration_Rep field of the proper constant. Note that this
7895 -- will not work for types Character/Wide_[Wide-]Character, since no
7896 -- real entities are created for the enumeration literals, but that
7897 -- does not matter since these two types do not have non-standard
7898 -- representations anyway.
7900 if Is_Enumeration_Type (P_Type)
7901 and then Has_Non_Standard_Rep (P_Type)
7902 then
7903 Fold_Uint (N, Enumeration_Rep (Expr_Value_E (E1)), Static);
7905 -- For enumeration types with standard representations and all
7906 -- other cases (i.e. all integer and modular types), Enum_Rep
7907 -- is equivalent to Pos.
7909 else
7910 Fold_Uint (N, Expr_Value (E1), Static);
7911 end if;
7913 --------------
7914 -- Enum_Val --
7915 --------------
7917 when Attribute_Enum_Val => Enum_Val : declare
7918 Lit : Node_Id;
7920 begin
7921 -- We have something like Enum_Type'Enum_Val (23), so search for a
7922 -- corresponding value in the list of Enum_Rep values for the type.
7924 Lit := First_Literal (P_Base_Type);
7925 loop
7926 if Enumeration_Rep (Lit) = Expr_Value (E1) then
7927 Fold_Uint (N, Enumeration_Pos (Lit), Static);
7928 exit;
7929 end if;
7931 Next_Literal (Lit);
7933 if No (Lit) then
7934 Apply_Compile_Time_Constraint_Error
7935 (N, "no representation value matches",
7936 CE_Range_Check_Failed,
7937 Warn => not Static);
7938 exit;
7939 end if;
7940 end loop;
7941 end Enum_Val;
7943 -------------
7944 -- Epsilon --
7945 -------------
7947 when Attribute_Epsilon =>
7949 -- Ada 83 attribute is defined as (RM83 3.5.8)
7951 -- T'Epsilon = 2.0**(1 - T'Mantissa)
7953 Fold_Ureal (N, Ureal_2 ** (1 - Mantissa), True);
7955 --------------
7956 -- Exponent --
7957 --------------
7959 when Attribute_Exponent =>
7960 Fold_Uint (N,
7961 Eval_Fat.Exponent (P_Base_Type, Expr_Value_R (E1)), Static);
7963 -----------
7964 -- First --
7965 -----------
7967 when Attribute_First => First_Attr :
7968 begin
7969 Set_Bounds;
7971 if Compile_Time_Known_Value (Lo_Bound) then
7972 if Is_Real_Type (P_Type) then
7973 Fold_Ureal (N, Expr_Value_R (Lo_Bound), Static);
7974 else
7975 Fold_Uint (N, Expr_Value (Lo_Bound), Static);
7976 end if;
7978 else
7979 Check_Concurrent_Discriminant (Lo_Bound);
7980 end if;
7981 end First_Attr;
7983 -----------------
7984 -- First_Valid --
7985 -----------------
7987 when Attribute_First_Valid => First_Valid :
7988 begin
7989 if Has_Predicates (P_Type)
7990 and then Has_Static_Predicate (P_Type)
7991 then
7992 declare
7993 FirstN : constant Node_Id :=
7994 First (Static_Discrete_Predicate (P_Type));
7995 begin
7996 if Nkind (FirstN) = N_Range then
7997 Fold_Uint (N, Expr_Value (Low_Bound (FirstN)), Static);
7998 else
7999 Fold_Uint (N, Expr_Value (FirstN), Static);
8000 end if;
8001 end;
8003 else
8004 Set_Bounds;
8005 Fold_Uint (N, Expr_Value (Lo_Bound), Static);
8006 end if;
8007 end First_Valid;
8009 -----------------
8010 -- Fixed_Value --
8011 -----------------
8013 when Attribute_Fixed_Value =>
8014 null;
8016 -----------
8017 -- Floor --
8018 -----------
8020 when Attribute_Floor =>
8021 Fold_Ureal
8022 (N, Eval_Fat.Floor (P_Base_Type, Expr_Value_R (E1)), Static);
8024 ----------
8025 -- Fore --
8026 ----------
8028 when Attribute_Fore =>
8029 if Compile_Time_Known_Bounds (P_Type) then
8030 Fold_Uint (N, UI_From_Int (Fore_Value), Static);
8031 end if;
8033 --------------
8034 -- Fraction --
8035 --------------
8037 when Attribute_Fraction =>
8038 Fold_Ureal
8039 (N, Eval_Fat.Fraction (P_Base_Type, Expr_Value_R (E1)), Static);
8041 -----------------------
8042 -- Has_Access_Values --
8043 -----------------------
8045 when Attribute_Has_Access_Values =>
8046 Rewrite (N, New_Occurrence_Of
8047 (Boolean_Literals (Has_Access_Values (P_Root_Type)), Loc));
8048 Analyze_And_Resolve (N, Standard_Boolean);
8050 -----------------------
8051 -- Has_Discriminants --
8052 -----------------------
8054 when Attribute_Has_Discriminants =>
8055 Rewrite (N, New_Occurrence_Of (
8056 Boolean_Literals (Has_Discriminants (P_Entity)), Loc));
8057 Analyze_And_Resolve (N, Standard_Boolean);
8059 ----------------------
8060 -- Has_Same_Storage --
8061 ----------------------
8063 when Attribute_Has_Same_Storage =>
8064 null;
8066 -----------------------
8067 -- Has_Tagged_Values --
8068 -----------------------
8070 when Attribute_Has_Tagged_Values =>
8071 Rewrite (N, New_Occurrence_Of
8072 (Boolean_Literals (Has_Tagged_Component (P_Root_Type)), Loc));
8073 Analyze_And_Resolve (N, Standard_Boolean);
8075 --------------
8076 -- Identity --
8077 --------------
8079 when Attribute_Identity =>
8080 null;
8082 -----------
8083 -- Image --
8084 -----------
8086 -- Image is a scalar attribute, but is never static, because it is
8087 -- not a static function (having a non-scalar argument (RM 4.9(22))
8088 -- However, we can constant-fold the image of an enumeration literal
8089 -- if names are available.
8091 when Attribute_Image =>
8092 if Is_Entity_Name (E1)
8093 and then Ekind (Entity (E1)) = E_Enumeration_Literal
8094 and then not Discard_Names (First_Subtype (Etype (E1)))
8095 and then not Global_Discard_Names
8096 then
8097 declare
8098 Lit : constant Entity_Id := Entity (E1);
8099 Str : String_Id;
8100 begin
8101 Start_String;
8102 Get_Unqualified_Decoded_Name_String (Chars (Lit));
8103 Set_Casing (All_Upper_Case);
8104 Store_String_Chars (Name_Buffer (1 .. Name_Len));
8105 Str := End_String;
8106 Rewrite (N, Make_String_Literal (Loc, Strval => Str));
8107 Analyze_And_Resolve (N, Standard_String);
8108 Set_Is_Static_Expression (N, False);
8109 end;
8110 end if;
8112 ---------
8113 -- Img --
8114 ---------
8116 -- Img is a scalar attribute, but is never static, because it is
8117 -- not a static function (having a non-scalar argument (RM 4.9(22))
8119 when Attribute_Img =>
8120 null;
8122 -------------------
8123 -- Integer_Value --
8124 -------------------
8126 -- We never try to fold Integer_Value (though perhaps we could???)
8128 when Attribute_Integer_Value =>
8129 null;
8131 -------------------
8132 -- Invalid_Value --
8133 -------------------
8135 -- Invalid_Value is a scalar attribute that is never static, because
8136 -- the value is by design out of range.
8138 when Attribute_Invalid_Value =>
8139 null;
8141 -----------
8142 -- Large --
8143 -----------
8145 when Attribute_Large =>
8147 -- For fixed-point, we use the identity:
8149 -- T'Large = (2.0**T'Mantissa - 1.0) * T'Small
8151 if Is_Fixed_Point_Type (P_Type) then
8152 Rewrite (N,
8153 Make_Op_Multiply (Loc,
8154 Left_Opnd =>
8155 Make_Op_Subtract (Loc,
8156 Left_Opnd =>
8157 Make_Op_Expon (Loc,
8158 Left_Opnd =>
8159 Make_Real_Literal (Loc, Ureal_2),
8160 Right_Opnd =>
8161 Make_Attribute_Reference (Loc,
8162 Prefix => P,
8163 Attribute_Name => Name_Mantissa)),
8164 Right_Opnd => Make_Real_Literal (Loc, Ureal_1)),
8166 Right_Opnd =>
8167 Make_Real_Literal (Loc, Small_Value (Entity (P)))));
8169 Analyze_And_Resolve (N, C_Type);
8171 -- Floating-point (Ada 83 compatibility)
8173 else
8174 -- Ada 83 attribute is defined as (RM83 3.5.8)
8176 -- T'Large = 2.0**T'Emax * (1.0 - 2.0**(-T'Mantissa))
8178 -- where
8180 -- T'Emax = 4 * T'Mantissa
8182 Fold_Ureal
8184 Ureal_2 ** (4 * Mantissa) * (Ureal_1 - Ureal_2 ** (-Mantissa)),
8185 True);
8186 end if;
8188 ---------------
8189 -- Lock_Free --
8190 ---------------
8192 when Attribute_Lock_Free => Lock_Free : declare
8193 V : constant Entity_Id := Boolean_Literals (Uses_Lock_Free (P_Type));
8195 begin
8196 Rewrite (N, New_Occurrence_Of (V, Loc));
8198 -- Analyze and resolve as boolean. Note that this attribute is a
8199 -- static attribute in GNAT.
8201 Analyze_And_Resolve (N, Standard_Boolean);
8202 Static := True;
8203 Set_Is_Static_Expression (N, True);
8204 end Lock_Free;
8206 ----------
8207 -- Last --
8208 ----------
8210 when Attribute_Last => Last_Attr :
8211 begin
8212 Set_Bounds;
8214 if Compile_Time_Known_Value (Hi_Bound) then
8215 if Is_Real_Type (P_Type) then
8216 Fold_Ureal (N, Expr_Value_R (Hi_Bound), Static);
8217 else
8218 Fold_Uint (N, Expr_Value (Hi_Bound), Static);
8219 end if;
8221 else
8222 Check_Concurrent_Discriminant (Hi_Bound);
8223 end if;
8224 end Last_Attr;
8226 ----------------
8227 -- Last_Valid --
8228 ----------------
8230 when Attribute_Last_Valid => Last_Valid :
8231 begin
8232 if Has_Predicates (P_Type)
8233 and then Has_Static_Predicate (P_Type)
8234 then
8235 declare
8236 LastN : constant Node_Id :=
8237 Last (Static_Discrete_Predicate (P_Type));
8238 begin
8239 if Nkind (LastN) = N_Range then
8240 Fold_Uint (N, Expr_Value (High_Bound (LastN)), Static);
8241 else
8242 Fold_Uint (N, Expr_Value (LastN), Static);
8243 end if;
8244 end;
8246 else
8247 Set_Bounds;
8248 Fold_Uint (N, Expr_Value (Hi_Bound), Static);
8249 end if;
8250 end Last_Valid;
8252 ------------------
8253 -- Leading_Part --
8254 ------------------
8256 when Attribute_Leading_Part =>
8257 Fold_Ureal
8259 Eval_Fat.Leading_Part
8260 (P_Base_Type, Expr_Value_R (E1), Expr_Value (E2)),
8261 Static);
8263 ------------
8264 -- Length --
8265 ------------
8267 when Attribute_Length => Length : declare
8268 Ind : Node_Id;
8270 begin
8271 -- If any index type is a formal type, or derived from one, the
8272 -- bounds are not static. Treating them as static can produce
8273 -- spurious warnings or improper constant folding.
8275 Ind := First_Index (P_Type);
8276 while Present (Ind) loop
8277 if Is_Generic_Type (Root_Type (Etype (Ind))) then
8278 return;
8279 end if;
8281 Next_Index (Ind);
8282 end loop;
8284 Set_Bounds;
8286 -- For two compile time values, we can compute length
8288 if Compile_Time_Known_Value (Lo_Bound)
8289 and then Compile_Time_Known_Value (Hi_Bound)
8290 then
8291 Fold_Uint (N,
8292 UI_Max (0, 1 + (Expr_Value (Hi_Bound) - Expr_Value (Lo_Bound))),
8293 Static);
8294 end if;
8296 -- One more case is where Hi_Bound and Lo_Bound are compile-time
8297 -- comparable, and we can figure out the difference between them.
8299 declare
8300 Diff : aliased Uint;
8302 begin
8303 case
8304 Compile_Time_Compare
8305 (Lo_Bound, Hi_Bound, Diff'Access, Assume_Valid => False)
8307 when EQ =>
8308 Fold_Uint (N, Uint_1, Static);
8310 when GT =>
8311 Fold_Uint (N, Uint_0, Static);
8313 when LT =>
8314 if Diff /= No_Uint then
8315 Fold_Uint (N, Diff + 1, Static);
8316 end if;
8318 when others =>
8319 null;
8320 end case;
8321 end;
8322 end Length;
8324 ----------------
8325 -- Loop_Entry --
8326 ----------------
8328 -- Loop_Entry acts as an alias of a constant initialized to the prefix
8329 -- of the said attribute at the point of entry into the related loop. As
8330 -- such, the attribute reference does not need to be evaluated because
8331 -- the prefix is the one that is evaluted.
8333 when Attribute_Loop_Entry =>
8334 null;
8336 -------------
8337 -- Machine --
8338 -------------
8340 when Attribute_Machine =>
8341 Fold_Ureal
8343 Eval_Fat.Machine
8344 (P_Base_Type, Expr_Value_R (E1), Eval_Fat.Round, N),
8345 Static);
8347 ------------------
8348 -- Machine_Emax --
8349 ------------------
8351 when Attribute_Machine_Emax =>
8352 Fold_Uint (N, Machine_Emax_Value (P_Type), Static);
8354 ------------------
8355 -- Machine_Emin --
8356 ------------------
8358 when Attribute_Machine_Emin =>
8359 Fold_Uint (N, Machine_Emin_Value (P_Type), Static);
8361 ----------------------
8362 -- Machine_Mantissa --
8363 ----------------------
8365 when Attribute_Machine_Mantissa =>
8366 Fold_Uint (N, Machine_Mantissa_Value (P_Type), Static);
8368 -----------------------
8369 -- Machine_Overflows --
8370 -----------------------
8372 when Attribute_Machine_Overflows =>
8374 -- Always true for fixed-point
8376 if Is_Fixed_Point_Type (P_Type) then
8377 Fold_Uint (N, True_Value, Static);
8379 -- Floating point case
8381 else
8382 Fold_Uint (N,
8383 UI_From_Int (Boolean'Pos (Machine_Overflows_On_Target)),
8384 Static);
8385 end if;
8387 -------------------
8388 -- Machine_Radix --
8389 -------------------
8391 when Attribute_Machine_Radix =>
8392 if Is_Fixed_Point_Type (P_Type) then
8393 if Is_Decimal_Fixed_Point_Type (P_Type)
8394 and then Machine_Radix_10 (P_Type)
8395 then
8396 Fold_Uint (N, Uint_10, Static);
8397 else
8398 Fold_Uint (N, Uint_2, Static);
8399 end if;
8401 -- All floating-point type always have radix 2
8403 else
8404 Fold_Uint (N, Uint_2, Static);
8405 end if;
8407 ----------------------
8408 -- Machine_Rounding --
8409 ----------------------
8411 -- Note: for the folding case, it is fine to treat Machine_Rounding
8412 -- exactly the same way as Rounding, since this is one of the allowed
8413 -- behaviors, and performance is not an issue here. It might be a bit
8414 -- better to give the same result as it would give at run time, even
8415 -- though the non-determinism is certainly permitted.
8417 when Attribute_Machine_Rounding =>
8418 Fold_Ureal
8419 (N, Eval_Fat.Rounding (P_Base_Type, Expr_Value_R (E1)), Static);
8421 --------------------
8422 -- Machine_Rounds --
8423 --------------------
8425 when Attribute_Machine_Rounds =>
8427 -- Always False for fixed-point
8429 if Is_Fixed_Point_Type (P_Type) then
8430 Fold_Uint (N, False_Value, Static);
8432 -- Else yield proper floating-point result
8434 else
8435 Fold_Uint
8436 (N, UI_From_Int (Boolean'Pos (Machine_Rounds_On_Target)),
8437 Static);
8438 end if;
8440 ------------------
8441 -- Machine_Size --
8442 ------------------
8444 -- Note: Machine_Size is identical to Object_Size
8446 when Attribute_Machine_Size => Machine_Size : declare
8447 P_TypeA : constant Entity_Id := Underlying_Type (P_Type);
8449 begin
8450 if Known_Esize (P_TypeA) then
8451 Fold_Uint (N, Esize (P_TypeA), Static);
8452 end if;
8453 end Machine_Size;
8455 --------------
8456 -- Mantissa --
8457 --------------
8459 when Attribute_Mantissa =>
8461 -- Fixed-point mantissa
8463 if Is_Fixed_Point_Type (P_Type) then
8465 -- Compile time foldable case
8467 if Compile_Time_Known_Value (Type_Low_Bound (P_Type))
8468 and then
8469 Compile_Time_Known_Value (Type_High_Bound (P_Type))
8470 then
8471 -- The calculation of the obsolete Ada 83 attribute Mantissa
8472 -- is annoying, because of AI00143, quoted here:
8474 -- !question 84-01-10
8476 -- Consider the model numbers for F:
8478 -- type F is delta 1.0 range -7.0 .. 8.0;
8480 -- The wording requires that F'MANTISSA be the SMALLEST
8481 -- integer number for which each bound of the specified
8482 -- range is either a model number or lies at most small
8483 -- distant from a model number. This means F'MANTISSA
8484 -- is required to be 3 since the range -7.0 .. 7.0 fits
8485 -- in 3 signed bits, and 8 is "at most" 1.0 from a model
8486 -- number, namely, 7. Is this analysis correct? Note that
8487 -- this implies the upper bound of the range is not
8488 -- represented as a model number.
8490 -- !response 84-03-17
8492 -- The analysis is correct. The upper and lower bounds for
8493 -- a fixed point type can lie outside the range of model
8494 -- numbers.
8496 declare
8497 Siz : Uint;
8498 LBound : Ureal;
8499 UBound : Ureal;
8500 Bound : Ureal;
8501 Max_Man : Uint;
8503 begin
8504 LBound := Expr_Value_R (Type_Low_Bound (P_Type));
8505 UBound := Expr_Value_R (Type_High_Bound (P_Type));
8506 Bound := UR_Max (UR_Abs (LBound), UR_Abs (UBound));
8507 Max_Man := UR_Trunc (Bound / Small_Value (P_Type));
8509 -- If the Bound is exactly a model number, i.e. a multiple
8510 -- of Small, then we back it off by one to get the integer
8511 -- value that must be representable.
8513 if Small_Value (P_Type) * Max_Man = Bound then
8514 Max_Man := Max_Man - 1;
8515 end if;
8517 -- Now find corresponding size = Mantissa value
8519 Siz := Uint_0;
8520 while 2 ** Siz < Max_Man loop
8521 Siz := Siz + 1;
8522 end loop;
8524 Fold_Uint (N, Siz, Static);
8525 end;
8527 else
8528 -- The case of dynamic bounds cannot be evaluated at compile
8529 -- time. Instead we use a runtime routine (see Exp_Attr).
8531 null;
8532 end if;
8534 -- Floating-point Mantissa
8536 else
8537 Fold_Uint (N, Mantissa, Static);
8538 end if;
8540 ---------
8541 -- Max --
8542 ---------
8544 when Attribute_Max => Max :
8545 begin
8546 if Is_Real_Type (P_Type) then
8547 Fold_Ureal
8548 (N, UR_Max (Expr_Value_R (E1), Expr_Value_R (E2)), Static);
8549 else
8550 Fold_Uint (N, UI_Max (Expr_Value (E1), Expr_Value (E2)), Static);
8551 end if;
8552 end Max;
8554 ----------------------------------
8555 -- Max_Alignment_For_Allocation --
8556 ----------------------------------
8558 -- Max_Alignment_For_Allocation is usually the Alignment. However,
8559 -- arrays are allocated with dope, so we need to take into account both
8560 -- the alignment of the array, which comes from the component alignment,
8561 -- and the alignment of the dope. Also, if the alignment is unknown, we
8562 -- use the max (it's OK to be pessimistic).
8564 when Attribute_Max_Alignment_For_Allocation =>
8565 declare
8566 A : Uint := UI_From_Int (Ttypes.Maximum_Alignment);
8567 begin
8568 if Known_Alignment (P_Type) and then
8569 (not Is_Array_Type (P_Type) or else Alignment (P_Type) > A)
8570 then
8571 A := Alignment (P_Type);
8572 end if;
8574 Fold_Uint (N, A, Static);
8575 end;
8577 ----------------------------------
8578 -- Max_Size_In_Storage_Elements --
8579 ----------------------------------
8581 -- Max_Size_In_Storage_Elements is simply the Size rounded up to a
8582 -- Storage_Unit boundary. We can fold any cases for which the size
8583 -- is known by the front end.
8585 when Attribute_Max_Size_In_Storage_Elements =>
8586 if Known_Esize (P_Type) then
8587 Fold_Uint (N,
8588 (Esize (P_Type) + System_Storage_Unit - 1) /
8589 System_Storage_Unit,
8590 Static);
8591 end if;
8593 --------------------
8594 -- Mechanism_Code --
8595 --------------------
8597 when Attribute_Mechanism_Code =>
8598 declare
8599 Val : Int;
8600 Formal : Entity_Id;
8601 Mech : Mechanism_Type;
8603 begin
8604 if No (E1) then
8605 Mech := Mechanism (P_Entity);
8607 else
8608 Val := UI_To_Int (Expr_Value (E1));
8610 Formal := First_Formal (P_Entity);
8611 for J in 1 .. Val - 1 loop
8612 Next_Formal (Formal);
8613 end loop;
8614 Mech := Mechanism (Formal);
8615 end if;
8617 if Mech < 0 then
8618 Fold_Uint (N, UI_From_Int (Int (-Mech)), Static);
8619 end if;
8620 end;
8622 ---------
8623 -- Min --
8624 ---------
8626 when Attribute_Min => Min :
8627 begin
8628 if Is_Real_Type (P_Type) then
8629 Fold_Ureal
8630 (N, UR_Min (Expr_Value_R (E1), Expr_Value_R (E2)), Static);
8631 else
8632 Fold_Uint
8633 (N, UI_Min (Expr_Value (E1), Expr_Value (E2)), Static);
8634 end if;
8635 end Min;
8637 ---------
8638 -- Mod --
8639 ---------
8641 when Attribute_Mod =>
8642 Fold_Uint
8643 (N, UI_Mod (Expr_Value (E1), Modulus (P_Base_Type)), Static);
8645 -----------
8646 -- Model --
8647 -----------
8649 when Attribute_Model =>
8650 Fold_Ureal
8651 (N, Eval_Fat.Model (P_Base_Type, Expr_Value_R (E1)), Static);
8653 ----------------
8654 -- Model_Emin --
8655 ----------------
8657 when Attribute_Model_Emin =>
8658 Fold_Uint (N, Model_Emin_Value (P_Base_Type), Static);
8660 -------------------
8661 -- Model_Epsilon --
8662 -------------------
8664 when Attribute_Model_Epsilon =>
8665 Fold_Ureal (N, Model_Epsilon_Value (P_Base_Type), Static);
8667 --------------------
8668 -- Model_Mantissa --
8669 --------------------
8671 when Attribute_Model_Mantissa =>
8672 Fold_Uint (N, Model_Mantissa_Value (P_Base_Type), Static);
8674 -----------------
8675 -- Model_Small --
8676 -----------------
8678 when Attribute_Model_Small =>
8679 Fold_Ureal (N, Model_Small_Value (P_Base_Type), Static);
8681 -------------
8682 -- Modulus --
8683 -------------
8685 when Attribute_Modulus =>
8686 Fold_Uint (N, Modulus (P_Type), Static);
8688 --------------------
8689 -- Null_Parameter --
8690 --------------------
8692 -- Cannot fold, we know the value sort of, but the whole point is
8693 -- that there is no way to talk about this imaginary value except
8694 -- by using the attribute, so we leave it the way it is.
8696 when Attribute_Null_Parameter =>
8697 null;
8699 -----------------
8700 -- Object_Size --
8701 -----------------
8703 -- The Object_Size attribute for a type returns the Esize of the
8704 -- type and can be folded if this value is known.
8706 when Attribute_Object_Size => Object_Size : declare
8707 P_TypeA : constant Entity_Id := Underlying_Type (P_Type);
8709 begin
8710 if Known_Esize (P_TypeA) then
8711 Fold_Uint (N, Esize (P_TypeA), Static);
8712 end if;
8713 end Object_Size;
8715 ----------------------
8716 -- Overlaps_Storage --
8717 ----------------------
8719 when Attribute_Overlaps_Storage =>
8720 null;
8722 -------------------------
8723 -- Passed_By_Reference --
8724 -------------------------
8726 -- Scalar types are never passed by reference
8728 when Attribute_Passed_By_Reference =>
8729 Fold_Uint (N, False_Value, Static);
8731 ---------
8732 -- Pos --
8733 ---------
8735 when Attribute_Pos =>
8736 Fold_Uint (N, Expr_Value (E1), Static);
8738 ----------
8739 -- Pred --
8740 ----------
8742 when Attribute_Pred => Pred :
8743 begin
8744 -- Floating-point case
8746 if Is_Floating_Point_Type (P_Type) then
8747 Fold_Ureal
8748 (N, Eval_Fat.Pred (P_Base_Type, Expr_Value_R (E1)), Static);
8750 -- Fixed-point case
8752 elsif Is_Fixed_Point_Type (P_Type) then
8753 Fold_Ureal
8754 (N, Expr_Value_R (E1) - Small_Value (P_Type), True);
8756 -- Modular integer case (wraps)
8758 elsif Is_Modular_Integer_Type (P_Type) then
8759 Fold_Uint (N, (Expr_Value (E1) - 1) mod Modulus (P_Type), Static);
8761 -- Other scalar cases
8763 else
8764 pragma Assert (Is_Scalar_Type (P_Type));
8766 if Is_Enumeration_Type (P_Type)
8767 and then Expr_Value (E1) =
8768 Expr_Value (Type_Low_Bound (P_Base_Type))
8769 then
8770 Apply_Compile_Time_Constraint_Error
8771 (N, "Pred of `&''First`",
8772 CE_Overflow_Check_Failed,
8773 Ent => P_Base_Type,
8774 Warn => not Static);
8776 Check_Expressions;
8777 return;
8778 end if;
8780 Fold_Uint (N, Expr_Value (E1) - 1, Static);
8781 end if;
8782 end Pred;
8784 -----------
8785 -- Range --
8786 -----------
8788 -- No processing required, because by this stage, Range has been
8789 -- replaced by First .. Last, so this branch can never be taken.
8791 when Attribute_Range =>
8792 raise Program_Error;
8794 ------------------
8795 -- Range_Length --
8796 ------------------
8798 when Attribute_Range_Length =>
8799 Set_Bounds;
8801 -- Can fold if both bounds are compile time known
8803 if Compile_Time_Known_Value (Hi_Bound)
8804 and then Compile_Time_Known_Value (Lo_Bound)
8805 then
8806 Fold_Uint (N,
8807 UI_Max
8808 (0, Expr_Value (Hi_Bound) - Expr_Value (Lo_Bound) + 1),
8809 Static);
8810 end if;
8812 -- One more case is where Hi_Bound and Lo_Bound are compile-time
8813 -- comparable, and we can figure out the difference between them.
8815 declare
8816 Diff : aliased Uint;
8818 begin
8819 case
8820 Compile_Time_Compare
8821 (Lo_Bound, Hi_Bound, Diff'Access, Assume_Valid => False)
8823 when EQ =>
8824 Fold_Uint (N, Uint_1, Static);
8826 when GT =>
8827 Fold_Uint (N, Uint_0, Static);
8829 when LT =>
8830 if Diff /= No_Uint then
8831 Fold_Uint (N, Diff + 1, Static);
8832 end if;
8834 when others =>
8835 null;
8836 end case;
8837 end;
8839 ---------
8840 -- Ref --
8841 ---------
8843 when Attribute_Ref =>
8844 Fold_Uint (N, Expr_Value (E1), Static);
8846 ---------------
8847 -- Remainder --
8848 ---------------
8850 when Attribute_Remainder => Remainder : declare
8851 X : constant Ureal := Expr_Value_R (E1);
8852 Y : constant Ureal := Expr_Value_R (E2);
8854 begin
8855 if UR_Is_Zero (Y) then
8856 Apply_Compile_Time_Constraint_Error
8857 (N, "division by zero in Remainder",
8858 CE_Overflow_Check_Failed,
8859 Warn => not Static);
8861 Check_Expressions;
8862 return;
8863 end if;
8865 Fold_Ureal (N, Eval_Fat.Remainder (P_Base_Type, X, Y), Static);
8866 end Remainder;
8868 -----------------
8869 -- Restriction --
8870 -----------------
8872 when Attribute_Restriction_Set => Restriction_Set : declare
8873 begin
8874 Rewrite (N, New_Occurrence_Of (Standard_False, Loc));
8875 Set_Is_Static_Expression (N);
8876 end Restriction_Set;
8878 -----------
8879 -- Round --
8880 -----------
8882 when Attribute_Round => Round :
8883 declare
8884 Sr : Ureal;
8885 Si : Uint;
8887 begin
8888 -- First we get the (exact result) in units of small
8890 Sr := Expr_Value_R (E1) / Small_Value (C_Type);
8892 -- Now round that exactly to an integer
8894 Si := UR_To_Uint (Sr);
8896 -- Finally the result is obtained by converting back to real
8898 Fold_Ureal (N, Si * Small_Value (C_Type), Static);
8899 end Round;
8901 --------------
8902 -- Rounding --
8903 --------------
8905 when Attribute_Rounding =>
8906 Fold_Ureal
8907 (N, Eval_Fat.Rounding (P_Base_Type, Expr_Value_R (E1)), Static);
8909 ---------------
8910 -- Safe_Emax --
8911 ---------------
8913 when Attribute_Safe_Emax =>
8914 Fold_Uint (N, Safe_Emax_Value (P_Type), Static);
8916 ----------------
8917 -- Safe_First --
8918 ----------------
8920 when Attribute_Safe_First =>
8921 Fold_Ureal (N, Safe_First_Value (P_Type), Static);
8923 ----------------
8924 -- Safe_Large --
8925 ----------------
8927 when Attribute_Safe_Large =>
8928 if Is_Fixed_Point_Type (P_Type) then
8929 Fold_Ureal
8930 (N, Expr_Value_R (Type_High_Bound (P_Base_Type)), Static);
8931 else
8932 Fold_Ureal (N, Safe_Last_Value (P_Type), Static);
8933 end if;
8935 ---------------
8936 -- Safe_Last --
8937 ---------------
8939 when Attribute_Safe_Last =>
8940 Fold_Ureal (N, Safe_Last_Value (P_Type), Static);
8942 ----------------
8943 -- Safe_Small --
8944 ----------------
8946 when Attribute_Safe_Small =>
8948 -- In Ada 95, the old Ada 83 attribute Safe_Small is redundant
8949 -- for fixed-point, since is the same as Small, but we implement
8950 -- it for backwards compatibility.
8952 if Is_Fixed_Point_Type (P_Type) then
8953 Fold_Ureal (N, Small_Value (P_Type), Static);
8955 -- Ada 83 Safe_Small for floating-point cases
8957 else
8958 Fold_Ureal (N, Model_Small_Value (P_Type), Static);
8959 end if;
8961 -----------
8962 -- Scale --
8963 -----------
8965 when Attribute_Scale =>
8966 Fold_Uint (N, Scale_Value (P_Type), Static);
8968 -------------
8969 -- Scaling --
8970 -------------
8972 when Attribute_Scaling =>
8973 Fold_Ureal
8975 Eval_Fat.Scaling
8976 (P_Base_Type, Expr_Value_R (E1), Expr_Value (E2)),
8977 Static);
8979 ------------------
8980 -- Signed_Zeros --
8981 ------------------
8983 when Attribute_Signed_Zeros =>
8984 Fold_Uint
8985 (N, UI_From_Int (Boolean'Pos (Has_Signed_Zeros (P_Type))), Static);
8987 ----------
8988 -- Size --
8989 ----------
8991 -- Size attribute returns the RM size. All scalar types can be folded,
8992 -- as well as any types for which the size is known by the front end,
8993 -- including any type for which a size attribute is specified. This is
8994 -- one of the places where it is annoying that a size of zero means two
8995 -- things (zero size for scalars, unspecified size for non-scalars).
8997 when Attribute_Size | Attribute_VADS_Size => Size : declare
8998 P_TypeA : constant Entity_Id := Underlying_Type (P_Type);
9000 begin
9001 if Is_Scalar_Type (P_TypeA) or else RM_Size (P_TypeA) /= Uint_0 then
9003 -- VADS_Size case
9005 if Id = Attribute_VADS_Size or else Use_VADS_Size then
9006 declare
9007 S : constant Node_Id := Size_Clause (P_TypeA);
9009 begin
9010 -- If a size clause applies, then use the size from it.
9011 -- This is one of the rare cases where we can use the
9012 -- Size_Clause field for a subtype when Has_Size_Clause
9013 -- is False. Consider:
9015 -- type x is range 1 .. 64;
9016 -- for x'size use 12;
9017 -- subtype y is x range 0 .. 3;
9019 -- Here y has a size clause inherited from x, but normally
9020 -- it does not apply, and y'size is 2. However, y'VADS_Size
9021 -- is indeed 12 and not 2.
9023 if Present (S)
9024 and then Is_OK_Static_Expression (Expression (S))
9025 then
9026 Fold_Uint (N, Expr_Value (Expression (S)), Static);
9028 -- If no size is specified, then we simply use the object
9029 -- size in the VADS_Size case (e.g. Natural'Size is equal
9030 -- to Integer'Size, not one less).
9032 else
9033 Fold_Uint (N, Esize (P_TypeA), Static);
9034 end if;
9035 end;
9037 -- Normal case (Size) in which case we want the RM_Size
9039 else
9040 Fold_Uint (N, RM_Size (P_TypeA), Static);
9041 end if;
9042 end if;
9043 end Size;
9045 -----------
9046 -- Small --
9047 -----------
9049 when Attribute_Small =>
9051 -- The floating-point case is present only for Ada 83 compatibility.
9052 -- Note that strictly this is an illegal addition, since we are
9053 -- extending an Ada 95 defined attribute, but we anticipate an
9054 -- ARG ruling that will permit this.
9056 if Is_Floating_Point_Type (P_Type) then
9058 -- Ada 83 attribute is defined as (RM83 3.5.8)
9060 -- T'Small = 2.0**(-T'Emax - 1)
9062 -- where
9064 -- T'Emax = 4 * T'Mantissa
9066 Fold_Ureal (N, Ureal_2 ** ((-(4 * Mantissa)) - 1), Static);
9068 -- Normal Ada 95 fixed-point case
9070 else
9071 Fold_Ureal (N, Small_Value (P_Type), True);
9072 end if;
9074 -----------------
9075 -- Stream_Size --
9076 -----------------
9078 when Attribute_Stream_Size =>
9079 null;
9081 ----------
9082 -- Succ --
9083 ----------
9085 when Attribute_Succ => Succ :
9086 begin
9087 -- Floating-point case
9089 if Is_Floating_Point_Type (P_Type) then
9090 Fold_Ureal
9091 (N, Eval_Fat.Succ (P_Base_Type, Expr_Value_R (E1)), Static);
9093 -- Fixed-point case
9095 elsif Is_Fixed_Point_Type (P_Type) then
9096 Fold_Ureal (N, Expr_Value_R (E1) + Small_Value (P_Type), Static);
9098 -- Modular integer case (wraps)
9100 elsif Is_Modular_Integer_Type (P_Type) then
9101 Fold_Uint (N, (Expr_Value (E1) + 1) mod Modulus (P_Type), Static);
9103 -- Other scalar cases
9105 else
9106 pragma Assert (Is_Scalar_Type (P_Type));
9108 if Is_Enumeration_Type (P_Type)
9109 and then Expr_Value (E1) =
9110 Expr_Value (Type_High_Bound (P_Base_Type))
9111 then
9112 Apply_Compile_Time_Constraint_Error
9113 (N, "Succ of `&''Last`",
9114 CE_Overflow_Check_Failed,
9115 Ent => P_Base_Type,
9116 Warn => not Static);
9118 Check_Expressions;
9119 return;
9120 else
9121 Fold_Uint (N, Expr_Value (E1) + 1, Static);
9122 end if;
9123 end if;
9124 end Succ;
9126 ----------------
9127 -- Truncation --
9128 ----------------
9130 when Attribute_Truncation =>
9131 Fold_Ureal
9133 Eval_Fat.Truncation (P_Base_Type, Expr_Value_R (E1)),
9134 Static);
9136 ----------------
9137 -- Type_Class --
9138 ----------------
9140 when Attribute_Type_Class => Type_Class : declare
9141 Typ : constant Entity_Id := Underlying_Type (P_Base_Type);
9142 Id : RE_Id;
9144 begin
9145 if Is_Descendent_Of_Address (Typ) then
9146 Id := RE_Type_Class_Address;
9148 elsif Is_Enumeration_Type (Typ) then
9149 Id := RE_Type_Class_Enumeration;
9151 elsif Is_Integer_Type (Typ) then
9152 Id := RE_Type_Class_Integer;
9154 elsif Is_Fixed_Point_Type (Typ) then
9155 Id := RE_Type_Class_Fixed_Point;
9157 elsif Is_Floating_Point_Type (Typ) then
9158 Id := RE_Type_Class_Floating_Point;
9160 elsif Is_Array_Type (Typ) then
9161 Id := RE_Type_Class_Array;
9163 elsif Is_Record_Type (Typ) then
9164 Id := RE_Type_Class_Record;
9166 elsif Is_Access_Type (Typ) then
9167 Id := RE_Type_Class_Access;
9169 elsif Is_Enumeration_Type (Typ) then
9170 Id := RE_Type_Class_Enumeration;
9172 elsif Is_Task_Type (Typ) then
9173 Id := RE_Type_Class_Task;
9175 -- We treat protected types like task types. It would make more
9176 -- sense to have another enumeration value, but after all the
9177 -- whole point of this feature is to be exactly DEC compatible,
9178 -- and changing the type Type_Class would not meet this requirement.
9180 elsif Is_Protected_Type (Typ) then
9181 Id := RE_Type_Class_Task;
9183 -- Not clear if there are any other possibilities, but if there
9184 -- are, then we will treat them as the address case.
9186 else
9187 Id := RE_Type_Class_Address;
9188 end if;
9190 Rewrite (N, New_Occurrence_Of (RTE (Id), Loc));
9191 end Type_Class;
9193 -----------------------
9194 -- Unbiased_Rounding --
9195 -----------------------
9197 when Attribute_Unbiased_Rounding =>
9198 Fold_Ureal
9200 Eval_Fat.Unbiased_Rounding (P_Base_Type, Expr_Value_R (E1)),
9201 Static);
9203 -------------------------
9204 -- Unconstrained_Array --
9205 -------------------------
9207 when Attribute_Unconstrained_Array => Unconstrained_Array : declare
9208 Typ : constant Entity_Id := Underlying_Type (P_Type);
9210 begin
9211 Rewrite (N, New_Occurrence_Of (
9212 Boolean_Literals (
9213 Is_Array_Type (P_Type)
9214 and then not Is_Constrained (Typ)), Loc));
9216 -- Analyze and resolve as boolean, note that this attribute is
9217 -- a static attribute in GNAT.
9219 Analyze_And_Resolve (N, Standard_Boolean);
9220 Static := True;
9221 Set_Is_Static_Expression (N, True);
9222 end Unconstrained_Array;
9224 -- Attribute Update is never static
9226 when Attribute_Update =>
9227 return;
9229 ---------------
9230 -- VADS_Size --
9231 ---------------
9233 -- Processing is shared with Size
9235 ---------
9236 -- Val --
9237 ---------
9239 when Attribute_Val => Val :
9240 begin
9241 if Expr_Value (E1) < Expr_Value (Type_Low_Bound (P_Base_Type))
9242 or else
9243 Expr_Value (E1) > Expr_Value (Type_High_Bound (P_Base_Type))
9244 then
9245 Apply_Compile_Time_Constraint_Error
9246 (N, "Val expression out of range",
9247 CE_Range_Check_Failed,
9248 Warn => not Static);
9250 Check_Expressions;
9251 return;
9253 else
9254 Fold_Uint (N, Expr_Value (E1), Static);
9255 end if;
9256 end Val;
9258 ----------------
9259 -- Value_Size --
9260 ----------------
9262 -- The Value_Size attribute for a type returns the RM size of the type.
9263 -- This an always be folded for scalar types, and can also be folded for
9264 -- non-scalar types if the size is set. This is one of the places where
9265 -- it is annoying that a size of zero means two things!
9267 when Attribute_Value_Size => Value_Size : declare
9268 P_TypeA : constant Entity_Id := Underlying_Type (P_Type);
9269 begin
9270 if Is_Scalar_Type (P_TypeA) or else RM_Size (P_TypeA) /= Uint_0 then
9271 Fold_Uint (N, RM_Size (P_TypeA), Static);
9272 end if;
9273 end Value_Size;
9275 -------------
9276 -- Version --
9277 -------------
9279 -- Version can never be static
9281 when Attribute_Version =>
9282 null;
9284 ----------------
9285 -- Wide_Image --
9286 ----------------
9288 -- Wide_Image is a scalar attribute, but is never static, because it
9289 -- is not a static function (having a non-scalar argument (RM 4.9(22))
9291 when Attribute_Wide_Image =>
9292 null;
9294 ---------------------
9295 -- Wide_Wide_Image --
9296 ---------------------
9298 -- Wide_Wide_Image is a scalar attribute but is never static, because it
9299 -- is not a static function (having a non-scalar argument (RM 4.9(22)).
9301 when Attribute_Wide_Wide_Image =>
9302 null;
9304 ---------------------
9305 -- Wide_Wide_Width --
9306 ---------------------
9308 -- Processing for Wide_Wide_Width is combined with Width
9310 ----------------
9311 -- Wide_Width --
9312 ----------------
9314 -- Processing for Wide_Width is combined with Width
9316 -----------
9317 -- Width --
9318 -----------
9320 -- This processing also handles the case of Wide_[Wide_]Width
9322 when Attribute_Width |
9323 Attribute_Wide_Width |
9324 Attribute_Wide_Wide_Width => Width :
9325 begin
9326 if Compile_Time_Known_Bounds (P_Type) then
9328 -- Floating-point types
9330 if Is_Floating_Point_Type (P_Type) then
9332 -- Width is zero for a null range (RM 3.5 (38))
9334 if Expr_Value_R (Type_High_Bound (P_Type)) <
9335 Expr_Value_R (Type_Low_Bound (P_Type))
9336 then
9337 Fold_Uint (N, Uint_0, Static);
9339 else
9340 -- For floating-point, we have +N.dddE+nnn where length
9341 -- of ddd is determined by type'Digits - 1, but is one
9342 -- if Digits is one (RM 3.5 (33)).
9344 -- nnn is set to 2 for Short_Float and Float (32 bit
9345 -- floats), and 3 for Long_Float and Long_Long_Float.
9346 -- For machines where Long_Long_Float is the IEEE
9347 -- extended precision type, the exponent takes 4 digits.
9349 declare
9350 Len : Int :=
9351 Int'Max (2, UI_To_Int (Digits_Value (P_Type)));
9353 begin
9354 if Esize (P_Type) <= 32 then
9355 Len := Len + 6;
9356 elsif Esize (P_Type) = 64 then
9357 Len := Len + 7;
9358 else
9359 Len := Len + 8;
9360 end if;
9362 Fold_Uint (N, UI_From_Int (Len), Static);
9363 end;
9364 end if;
9366 -- Fixed-point types
9368 elsif Is_Fixed_Point_Type (P_Type) then
9370 -- Width is zero for a null range (RM 3.5 (38))
9372 if Expr_Value (Type_High_Bound (P_Type)) <
9373 Expr_Value (Type_Low_Bound (P_Type))
9374 then
9375 Fold_Uint (N, Uint_0, Static);
9377 -- The non-null case depends on the specific real type
9379 else
9380 -- For fixed-point type width is Fore + 1 + Aft (RM 3.5(34))
9382 Fold_Uint
9383 (N, UI_From_Int (Fore_Value + 1) + Aft_Value (P_Type),
9384 Static);
9385 end if;
9387 -- Discrete types
9389 else
9390 declare
9391 R : constant Entity_Id := Root_Type (P_Type);
9392 Lo : constant Uint := Expr_Value (Type_Low_Bound (P_Type));
9393 Hi : constant Uint := Expr_Value (Type_High_Bound (P_Type));
9394 W : Nat;
9395 Wt : Nat;
9396 T : Uint;
9397 L : Node_Id;
9398 C : Character;
9400 begin
9401 -- Empty ranges
9403 if Lo > Hi then
9404 W := 0;
9406 -- Width for types derived from Standard.Character
9407 -- and Standard.Wide_[Wide_]Character.
9409 elsif Is_Standard_Character_Type (P_Type) then
9410 W := 0;
9412 -- Set W larger if needed
9414 for J in UI_To_Int (Lo) .. UI_To_Int (Hi) loop
9416 -- All wide characters look like Hex_hhhhhhhh
9418 if J > 255 then
9420 -- No need to compute this more than once
9422 exit;
9424 else
9425 C := Character'Val (J);
9427 -- Test for all cases where Character'Image
9428 -- yields an image that is longer than three
9429 -- characters. First the cases of Reserved_xxx
9430 -- names (length = 12).
9432 case C is
9433 when Reserved_128 | Reserved_129 |
9434 Reserved_132 | Reserved_153
9435 => Wt := 12;
9437 when BS | HT | LF | VT | FF | CR |
9438 SO | SI | EM | FS | GS | RS |
9439 US | RI | MW | ST | PM
9440 => Wt := 2;
9442 when NUL | SOH | STX | ETX | EOT |
9443 ENQ | ACK | BEL | DLE | DC1 |
9444 DC2 | DC3 | DC4 | NAK | SYN |
9445 ETB | CAN | SUB | ESC | DEL |
9446 BPH | NBH | NEL | SSA | ESA |
9447 HTS | HTJ | VTS | PLD | PLU |
9448 SS2 | SS3 | DCS | PU1 | PU2 |
9449 STS | CCH | SPA | EPA | SOS |
9450 SCI | CSI | OSC | APC
9451 => Wt := 3;
9453 when Space .. Tilde |
9454 No_Break_Space .. LC_Y_Diaeresis
9456 -- Special case of soft hyphen in Ada 2005
9458 if C = Character'Val (16#AD#)
9459 and then Ada_Version >= Ada_2005
9460 then
9461 Wt := 11;
9462 else
9463 Wt := 3;
9464 end if;
9465 end case;
9467 W := Int'Max (W, Wt);
9468 end if;
9469 end loop;
9471 -- Width for types derived from Standard.Boolean
9473 elsif R = Standard_Boolean then
9474 if Lo = 0 then
9475 W := 5; -- FALSE
9476 else
9477 W := 4; -- TRUE
9478 end if;
9480 -- Width for integer types
9482 elsif Is_Integer_Type (P_Type) then
9483 T := UI_Max (abs Lo, abs Hi);
9485 W := 2;
9486 while T >= 10 loop
9487 W := W + 1;
9488 T := T / 10;
9489 end loop;
9491 -- User declared enum type with discard names
9493 elsif Discard_Names (R) then
9495 -- If range is null, result is zero, that has already
9496 -- been dealt with, so what we need is the power of ten
9497 -- that accomodates the Pos of the largest value, which
9498 -- is the high bound of the range + one for the space.
9500 W := 1;
9501 T := Hi;
9502 while T /= 0 loop
9503 T := T / 10;
9504 W := W + 1;
9505 end loop;
9507 -- Only remaining possibility is user declared enum type
9508 -- with normal case of Discard_Names not active.
9510 else
9511 pragma Assert (Is_Enumeration_Type (P_Type));
9513 W := 0;
9514 L := First_Literal (P_Type);
9515 while Present (L) loop
9517 -- Only pay attention to in range characters
9519 if Lo <= Enumeration_Pos (L)
9520 and then Enumeration_Pos (L) <= Hi
9521 then
9522 -- For Width case, use decoded name
9524 if Id = Attribute_Width then
9525 Get_Decoded_Name_String (Chars (L));
9526 Wt := Nat (Name_Len);
9528 -- For Wide_[Wide_]Width, use encoded name, and
9529 -- then adjust for the encoding.
9531 else
9532 Get_Name_String (Chars (L));
9534 -- Character literals are always of length 3
9536 if Name_Buffer (1) = 'Q' then
9537 Wt := 3;
9539 -- Otherwise loop to adjust for upper/wide chars
9541 else
9542 Wt := Nat (Name_Len);
9544 for J in 1 .. Name_Len loop
9545 if Name_Buffer (J) = 'U' then
9546 Wt := Wt - 2;
9547 elsif Name_Buffer (J) = 'W' then
9548 Wt := Wt - 4;
9549 end if;
9550 end loop;
9551 end if;
9552 end if;
9554 W := Int'Max (W, Wt);
9555 end if;
9557 Next_Literal (L);
9558 end loop;
9559 end if;
9561 Fold_Uint (N, UI_From_Int (W), Static);
9562 end;
9563 end if;
9564 end if;
9565 end Width;
9567 -- The following attributes denote functions that cannot be folded
9569 when Attribute_From_Any |
9570 Attribute_To_Any |
9571 Attribute_TypeCode =>
9572 null;
9574 -- The following attributes can never be folded, and furthermore we
9575 -- should not even have entered the case statement for any of these.
9576 -- Note that in some cases, the values have already been folded as
9577 -- a result of the processing in Analyze_Attribute.
9579 when Attribute_Abort_Signal |
9580 Attribute_Access |
9581 Attribute_Address |
9582 Attribute_Address_Size |
9583 Attribute_Asm_Input |
9584 Attribute_Asm_Output |
9585 Attribute_Base |
9586 Attribute_Bit_Order |
9587 Attribute_Bit_Position |
9588 Attribute_Callable |
9589 Attribute_Caller |
9590 Attribute_Class |
9591 Attribute_Code_Address |
9592 Attribute_Compiler_Version |
9593 Attribute_Count |
9594 Attribute_Default_Bit_Order |
9595 Attribute_Default_Scalar_Storage_Order |
9596 Attribute_Elaborated |
9597 Attribute_Elab_Body |
9598 Attribute_Elab_Spec |
9599 Attribute_Elab_Subp_Body |
9600 Attribute_Enabled |
9601 Attribute_External_Tag |
9602 Attribute_Fast_Math |
9603 Attribute_First_Bit |
9604 Attribute_Input |
9605 Attribute_Last_Bit |
9606 Attribute_Library_Level |
9607 Attribute_Maximum_Alignment |
9608 Attribute_Old |
9609 Attribute_Output |
9610 Attribute_Partition_ID |
9611 Attribute_Pool_Address |
9612 Attribute_Position |
9613 Attribute_Priority |
9614 Attribute_Read |
9615 Attribute_Result |
9616 Attribute_Scalar_Storage_Order |
9617 Attribute_Simple_Storage_Pool |
9618 Attribute_Storage_Pool |
9619 Attribute_Storage_Size |
9620 Attribute_Storage_Unit |
9621 Attribute_Stub_Type |
9622 Attribute_System_Allocator_Alignment |
9623 Attribute_Tag |
9624 Attribute_Target_Name |
9625 Attribute_Terminated |
9626 Attribute_To_Address |
9627 Attribute_Type_Key |
9628 Attribute_UET_Address |
9629 Attribute_Unchecked_Access |
9630 Attribute_Universal_Literal_String |
9631 Attribute_Unrestricted_Access |
9632 Attribute_Valid |
9633 Attribute_Valid_Scalars |
9634 Attribute_Value |
9635 Attribute_Wchar_T_Size |
9636 Attribute_Wide_Value |
9637 Attribute_Wide_Wide_Value |
9638 Attribute_Word_Size |
9639 Attribute_Write =>
9641 raise Program_Error;
9642 end case;
9644 -- At the end of the case, one more check. If we did a static evaluation
9645 -- so that the result is now a literal, then set Is_Static_Expression
9646 -- in the constant only if the prefix type is a static subtype. For
9647 -- non-static subtypes, the folding is still OK, but not static.
9649 -- An exception is the GNAT attribute Constrained_Array which is
9650 -- defined to be a static attribute in all cases.
9652 if Nkind_In (N, N_Integer_Literal,
9653 N_Real_Literal,
9654 N_Character_Literal,
9655 N_String_Literal)
9656 or else (Is_Entity_Name (N)
9657 and then Ekind (Entity (N)) = E_Enumeration_Literal)
9658 then
9659 Set_Is_Static_Expression (N, Static);
9661 -- If this is still an attribute reference, then it has not been folded
9662 -- and that means that its expressions are in a non-static context.
9664 elsif Nkind (N) = N_Attribute_Reference then
9665 Check_Expressions;
9667 -- Note: the else case not covered here are odd cases where the
9668 -- processing has transformed the attribute into something other
9669 -- than a constant. Nothing more to do in such cases.
9671 else
9672 null;
9673 end if;
9674 end Eval_Attribute;
9676 ------------------------------
9677 -- Is_Anonymous_Tagged_Base --
9678 ------------------------------
9680 function Is_Anonymous_Tagged_Base
9681 (Anon : Entity_Id;
9682 Typ : Entity_Id) return Boolean
9684 begin
9685 return
9686 Anon = Current_Scope
9687 and then Is_Itype (Anon)
9688 and then Associated_Node_For_Itype (Anon) = Parent (Typ);
9689 end Is_Anonymous_Tagged_Base;
9691 --------------------------------
9692 -- Name_Implies_Lvalue_Prefix --
9693 --------------------------------
9695 function Name_Implies_Lvalue_Prefix (Nam : Name_Id) return Boolean is
9696 pragma Assert (Is_Attribute_Name (Nam));
9697 begin
9698 return Attribute_Name_Implies_Lvalue_Prefix (Get_Attribute_Id (Nam));
9699 end Name_Implies_Lvalue_Prefix;
9701 -----------------------
9702 -- Resolve_Attribute --
9703 -----------------------
9705 procedure Resolve_Attribute (N : Node_Id; Typ : Entity_Id) is
9706 Loc : constant Source_Ptr := Sloc (N);
9707 P : constant Node_Id := Prefix (N);
9708 Aname : constant Name_Id := Attribute_Name (N);
9709 Attr_Id : constant Attribute_Id := Get_Attribute_Id (Aname);
9710 Btyp : constant Entity_Id := Base_Type (Typ);
9711 Des_Btyp : Entity_Id;
9712 Index : Interp_Index;
9713 It : Interp;
9714 Nom_Subt : Entity_Id;
9716 procedure Accessibility_Message;
9717 -- Error, or warning within an instance, if the static accessibility
9718 -- rules of 3.10.2 are violated.
9720 ---------------------------
9721 -- Accessibility_Message --
9722 ---------------------------
9724 procedure Accessibility_Message is
9725 Indic : Node_Id := Parent (Parent (N));
9727 begin
9728 -- In an instance, this is a runtime check, but one we
9729 -- know will fail, so generate an appropriate warning.
9731 if In_Instance_Body then
9732 Error_Msg_Warn := SPARK_Mode /= On;
9733 Error_Msg_F
9734 ("non-local pointer cannot point to local object<<", P);
9735 Error_Msg_F ("\Program_Error [<<", P);
9736 Rewrite (N,
9737 Make_Raise_Program_Error (Loc,
9738 Reason => PE_Accessibility_Check_Failed));
9739 Set_Etype (N, Typ);
9740 return;
9742 else
9743 Error_Msg_F ("non-local pointer cannot point to local object", P);
9745 -- Check for case where we have a missing access definition
9747 if Is_Record_Type (Current_Scope)
9748 and then
9749 Nkind_In (Parent (N), N_Discriminant_Association,
9750 N_Index_Or_Discriminant_Constraint)
9751 then
9752 Indic := Parent (Parent (N));
9753 while Present (Indic)
9754 and then Nkind (Indic) /= N_Subtype_Indication
9755 loop
9756 Indic := Parent (Indic);
9757 end loop;
9759 if Present (Indic) then
9760 Error_Msg_NE
9761 ("\use an access definition for" &
9762 " the access discriminant of&",
9763 N, Entity (Subtype_Mark (Indic)));
9764 end if;
9765 end if;
9766 end if;
9767 end Accessibility_Message;
9769 -- Start of processing for Resolve_Attribute
9771 begin
9772 -- If error during analysis, no point in continuing, except for array
9773 -- types, where we get better recovery by using unconstrained indexes
9774 -- than nothing at all (see Check_Array_Type).
9776 if Error_Posted (N)
9777 and then Attr_Id /= Attribute_First
9778 and then Attr_Id /= Attribute_Last
9779 and then Attr_Id /= Attribute_Length
9780 and then Attr_Id /= Attribute_Range
9781 then
9782 return;
9783 end if;
9785 -- If attribute was universal type, reset to actual type
9787 if Etype (N) = Universal_Integer
9788 or else Etype (N) = Universal_Real
9789 then
9790 Set_Etype (N, Typ);
9791 end if;
9793 -- Remaining processing depends on attribute
9795 case Attr_Id is
9797 ------------
9798 -- Access --
9799 ------------
9801 -- For access attributes, if the prefix denotes an entity, it is
9802 -- interpreted as a name, never as a call. It may be overloaded,
9803 -- in which case resolution uses the profile of the context type.
9804 -- Otherwise prefix must be resolved.
9806 when Attribute_Access
9807 | Attribute_Unchecked_Access
9808 | Attribute_Unrestricted_Access =>
9810 Access_Attribute :
9811 begin
9812 if Is_Variable (P) then
9813 Note_Possible_Modification (P, Sure => False);
9814 end if;
9816 -- The following comes from a query concerning improper use of
9817 -- universal_access in equality tests involving anonymous access
9818 -- types. Another good reason for 'Ref, but for now disable the
9819 -- test, which breaks several filed tests???
9821 if Ekind (Typ) = E_Anonymous_Access_Type
9822 and then Nkind_In (Parent (N), N_Op_Eq, N_Op_Ne)
9823 and then False
9824 then
9825 Error_Msg_N ("need unique type to resolve 'Access", N);
9826 Error_Msg_N ("\qualify attribute with some access type", N);
9827 end if;
9829 -- Case where prefix is an entity name
9831 if Is_Entity_Name (P) then
9833 -- Deal with case where prefix itself is overloaded
9835 if Is_Overloaded (P) then
9836 Get_First_Interp (P, Index, It);
9837 while Present (It.Nam) loop
9838 if Type_Conformant (Designated_Type (Typ), It.Nam) then
9839 Set_Entity (P, It.Nam);
9841 -- The prefix is definitely NOT overloaded anymore at
9842 -- this point, so we reset the Is_Overloaded flag to
9843 -- avoid any confusion when reanalyzing the node.
9845 Set_Is_Overloaded (P, False);
9846 Set_Is_Overloaded (N, False);
9847 Generate_Reference (Entity (P), P);
9848 exit;
9849 end if;
9851 Get_Next_Interp (Index, It);
9852 end loop;
9854 -- If Prefix is a subprogram name, this reference freezes:
9856 -- If it is a type, there is nothing to resolve.
9857 -- If it is an object, complete its resolution.
9859 elsif Is_Overloadable (Entity (P)) then
9861 -- Avoid insertion of freeze actions in spec expression mode
9863 if not In_Spec_Expression then
9864 Freeze_Before (N, Entity (P));
9865 end if;
9867 -- Nothing to do if prefix is a type name
9869 elsif Is_Type (Entity (P)) then
9870 null;
9872 -- Otherwise non-overloaded other case, resolve the prefix
9874 else
9875 Resolve (P);
9876 end if;
9878 -- Some further error checks
9880 Error_Msg_Name_1 := Aname;
9882 if not Is_Entity_Name (P) then
9883 null;
9885 elsif Is_Overloadable (Entity (P))
9886 and then Is_Abstract_Subprogram (Entity (P))
9887 then
9888 Error_Msg_F ("prefix of % attribute cannot be abstract", P);
9889 Set_Etype (N, Any_Type);
9891 elsif Ekind (Entity (P)) = E_Enumeration_Literal then
9892 Error_Msg_F
9893 ("prefix of % attribute cannot be enumeration literal", P);
9894 Set_Etype (N, Any_Type);
9896 -- An attempt to take 'Access of a function that renames an
9897 -- enumeration literal. Issue a specialized error message.
9899 elsif Ekind (Entity (P)) = E_Function
9900 and then Present (Alias (Entity (P)))
9901 and then Ekind (Alias (Entity (P))) = E_Enumeration_Literal
9902 then
9903 Error_Msg_F
9904 ("prefix of % attribute cannot be function renaming "
9905 & "an enumeration literal", P);
9906 Set_Etype (N, Any_Type);
9908 elsif Convention (Entity (P)) = Convention_Intrinsic then
9909 Error_Msg_F ("prefix of % attribute cannot be intrinsic", P);
9910 Set_Etype (N, Any_Type);
9911 end if;
9913 -- Assignments, return statements, components of aggregates,
9914 -- generic instantiations will require convention checks if
9915 -- the type is an access to subprogram. Given that there will
9916 -- also be accessibility checks on those, this is where the
9917 -- checks can eventually be centralized ???
9919 if Ekind_In (Btyp, E_Access_Subprogram_Type,
9920 E_Anonymous_Access_Subprogram_Type,
9921 E_Access_Protected_Subprogram_Type,
9922 E_Anonymous_Access_Protected_Subprogram_Type)
9923 then
9924 -- Deal with convention mismatch
9926 if Convention (Designated_Type (Btyp)) /=
9927 Convention (Entity (P))
9928 then
9929 Error_Msg_FE
9930 ("subprogram & has wrong convention", P, Entity (P));
9931 Error_Msg_Sloc := Sloc (Btyp);
9932 Error_Msg_FE ("\does not match & declared#", P, Btyp);
9934 if not Is_Itype (Btyp)
9935 and then not Has_Convention_Pragma (Btyp)
9936 then
9937 Error_Msg_FE
9938 ("\probable missing pragma Convention for &",
9939 P, Btyp);
9940 end if;
9942 else
9943 Check_Subtype_Conformant
9944 (New_Id => Entity (P),
9945 Old_Id => Designated_Type (Btyp),
9946 Err_Loc => P);
9947 end if;
9949 if Attr_Id = Attribute_Unchecked_Access then
9950 Error_Msg_Name_1 := Aname;
9951 Error_Msg_F
9952 ("attribute% cannot be applied to a subprogram", P);
9954 elsif Aname = Name_Unrestricted_Access then
9955 null; -- Nothing to check
9957 -- Check the static accessibility rule of 3.10.2(32).
9958 -- This rule also applies within the private part of an
9959 -- instantiation. This rule does not apply to anonymous
9960 -- access-to-subprogram types in access parameters.
9962 elsif Attr_Id = Attribute_Access
9963 and then not In_Instance_Body
9964 and then
9965 (Ekind (Btyp) = E_Access_Subprogram_Type
9966 or else Is_Local_Anonymous_Access (Btyp))
9967 and then Subprogram_Access_Level (Entity (P)) >
9968 Type_Access_Level (Btyp)
9969 then
9970 Error_Msg_F
9971 ("subprogram must not be deeper than access type", P);
9973 -- Check the restriction of 3.10.2(32) that disallows the
9974 -- access attribute within a generic body when the ultimate
9975 -- ancestor of the type of the attribute is declared outside
9976 -- of the generic unit and the subprogram is declared within
9977 -- that generic unit. This includes any such attribute that
9978 -- occurs within the body of a generic unit that is a child
9979 -- of the generic unit where the subprogram is declared.
9981 -- The rule also prohibits applying the attribute when the
9982 -- access type is a generic formal access type (since the
9983 -- level of the actual type is not known). This restriction
9984 -- does not apply when the attribute type is an anonymous
9985 -- access-to-subprogram type. Note that this check was
9986 -- revised by AI-229, because the originally Ada 95 rule
9987 -- was too lax. The original rule only applied when the
9988 -- subprogram was declared within the body of the generic,
9989 -- which allowed the possibility of dangling references).
9990 -- The rule was also too strict in some case, in that it
9991 -- didn't permit the access to be declared in the generic
9992 -- spec, whereas the revised rule does (as long as it's not
9993 -- a formal type).
9995 -- There are a couple of subtleties of the test for applying
9996 -- the check that are worth noting. First, we only apply it
9997 -- when the levels of the subprogram and access type are the
9998 -- same (the case where the subprogram is statically deeper
9999 -- was applied above, and the case where the type is deeper
10000 -- is always safe). Second, we want the check to apply
10001 -- within nested generic bodies and generic child unit
10002 -- bodies, but not to apply to an attribute that appears in
10003 -- the generic unit's specification. This is done by testing
10004 -- that the attribute's innermost enclosing generic body is
10005 -- not the same as the innermost generic body enclosing the
10006 -- generic unit where the subprogram is declared (we don't
10007 -- want the check to apply when the access attribute is in
10008 -- the spec and there's some other generic body enclosing
10009 -- generic). Finally, there's no point applying the check
10010 -- when within an instance, because any violations will have
10011 -- been caught by the compilation of the generic unit.
10013 -- We relax this check in Relaxed_RM_Semantics mode for
10014 -- compatibility with legacy code for use by Ada source
10015 -- code analyzers (e.g. CodePeer).
10017 elsif Attr_Id = Attribute_Access
10018 and then not Relaxed_RM_Semantics
10019 and then not In_Instance
10020 and then Present (Enclosing_Generic_Unit (Entity (P)))
10021 and then Present (Enclosing_Generic_Body (N))
10022 and then Enclosing_Generic_Body (N) /=
10023 Enclosing_Generic_Body
10024 (Enclosing_Generic_Unit (Entity (P)))
10025 and then Subprogram_Access_Level (Entity (P)) =
10026 Type_Access_Level (Btyp)
10027 and then Ekind (Btyp) /=
10028 E_Anonymous_Access_Subprogram_Type
10029 and then Ekind (Btyp) /=
10030 E_Anonymous_Access_Protected_Subprogram_Type
10031 then
10032 -- The attribute type's ultimate ancestor must be
10033 -- declared within the same generic unit as the
10034 -- subprogram is declared. The error message is
10035 -- specialized to say "ancestor" for the case where the
10036 -- access type is not its own ancestor, since saying
10037 -- simply "access type" would be very confusing.
10039 if Enclosing_Generic_Unit (Entity (P)) /=
10040 Enclosing_Generic_Unit (Root_Type (Btyp))
10041 then
10042 Error_Msg_N
10043 ("''Access attribute not allowed in generic body",
10046 if Root_Type (Btyp) = Btyp then
10047 Error_Msg_NE
10048 ("\because " &
10049 "access type & is declared outside " &
10050 "generic unit (RM 3.10.2(32))", N, Btyp);
10051 else
10052 Error_Msg_NE
10053 ("\because ancestor of " &
10054 "access type & is declared outside " &
10055 "generic unit (RM 3.10.2(32))", N, Btyp);
10056 end if;
10058 Error_Msg_NE
10059 ("\move ''Access to private part, or " &
10060 "(Ada 2005) use anonymous access type instead of &",
10061 N, Btyp);
10063 -- If the ultimate ancestor of the attribute's type is
10064 -- a formal type, then the attribute is illegal because
10065 -- the actual type might be declared at a higher level.
10066 -- The error message is specialized to say "ancestor"
10067 -- for the case where the access type is not its own
10068 -- ancestor, since saying simply "access type" would be
10069 -- very confusing.
10071 elsif Is_Generic_Type (Root_Type (Btyp)) then
10072 if Root_Type (Btyp) = Btyp then
10073 Error_Msg_N
10074 ("access type must not be a generic formal type",
10076 else
10077 Error_Msg_N
10078 ("ancestor access type must not be a generic " &
10079 "formal type", N);
10080 end if;
10081 end if;
10082 end if;
10083 end if;
10085 -- If this is a renaming, an inherited operation, or a
10086 -- subprogram instance, use the original entity. This may make
10087 -- the node type-inconsistent, so this transformation can only
10088 -- be done if the node will not be reanalyzed. In particular,
10089 -- if it is within a default expression, the transformation
10090 -- must be delayed until the default subprogram is created for
10091 -- it, when the enclosing subprogram is frozen.
10093 if Is_Entity_Name (P)
10094 and then Is_Overloadable (Entity (P))
10095 and then Present (Alias (Entity (P)))
10096 and then Expander_Active
10097 then
10098 Rewrite (P,
10099 New_Occurrence_Of (Alias (Entity (P)), Sloc (P)));
10100 end if;
10102 elsif Nkind (P) = N_Selected_Component
10103 and then Is_Overloadable (Entity (Selector_Name (P)))
10104 then
10105 -- Protected operation. If operation is overloaded, must
10106 -- disambiguate. Prefix that denotes protected object itself
10107 -- is resolved with its own type.
10109 if Attr_Id = Attribute_Unchecked_Access then
10110 Error_Msg_Name_1 := Aname;
10111 Error_Msg_F
10112 ("attribute% cannot be applied to protected operation", P);
10113 end if;
10115 Resolve (Prefix (P));
10116 Generate_Reference (Entity (Selector_Name (P)), P);
10118 -- Implement check implied by 3.10.2 (18.1/2) : F.all'access is
10119 -- statically illegal if F is an anonymous access to subprogram.
10121 elsif Nkind (P) = N_Explicit_Dereference
10122 and then Is_Entity_Name (Prefix (P))
10123 and then Ekind (Etype (Entity (Prefix (P)))) =
10124 E_Anonymous_Access_Subprogram_Type
10125 then
10126 Error_Msg_N ("anonymous access to subprogram "
10127 & "has deeper accessibility than any master", P);
10129 elsif Is_Overloaded (P) then
10131 -- Use the designated type of the context to disambiguate
10132 -- Note that this was not strictly conformant to Ada 95,
10133 -- but was the implementation adopted by most Ada 95 compilers.
10134 -- The use of the context type to resolve an Access attribute
10135 -- reference is now mandated in AI-235 for Ada 2005.
10137 declare
10138 Index : Interp_Index;
10139 It : Interp;
10141 begin
10142 Get_First_Interp (P, Index, It);
10143 while Present (It.Typ) loop
10144 if Covers (Designated_Type (Typ), It.Typ) then
10145 Resolve (P, It.Typ);
10146 exit;
10147 end if;
10149 Get_Next_Interp (Index, It);
10150 end loop;
10151 end;
10152 else
10153 Resolve (P);
10154 end if;
10156 -- X'Access is illegal if X denotes a constant and the access type
10157 -- is access-to-variable. Same for 'Unchecked_Access. The rule
10158 -- does not apply to 'Unrestricted_Access. If the reference is a
10159 -- default-initialized aggregate component for a self-referential
10160 -- type the reference is legal.
10162 if not (Ekind (Btyp) = E_Access_Subprogram_Type
10163 or else Ekind (Btyp) = E_Anonymous_Access_Subprogram_Type
10164 or else (Is_Record_Type (Btyp)
10165 and then
10166 Present (Corresponding_Remote_Type (Btyp)))
10167 or else Ekind (Btyp) = E_Access_Protected_Subprogram_Type
10168 or else Ekind (Btyp)
10169 = E_Anonymous_Access_Protected_Subprogram_Type
10170 or else Is_Access_Constant (Btyp)
10171 or else Is_Variable (P)
10172 or else Attr_Id = Attribute_Unrestricted_Access)
10173 then
10174 if Is_Entity_Name (P)
10175 and then Is_Type (Entity (P))
10176 then
10177 -- Legality of a self-reference through an access
10178 -- attribute has been verified in Analyze_Access_Attribute.
10180 null;
10182 elsif Comes_From_Source (N) then
10183 Error_Msg_F ("access-to-variable designates constant", P);
10184 end if;
10185 end if;
10187 Des_Btyp := Designated_Type (Btyp);
10189 if Ada_Version >= Ada_2005
10190 and then Is_Incomplete_Type (Des_Btyp)
10191 then
10192 -- Ada 2005 (AI-412): If the (sub)type is a limited view of an
10193 -- imported entity, and the non-limited view is visible, make
10194 -- use of it. If it is an incomplete subtype, use the base type
10195 -- in any case.
10197 if From_Limited_With (Des_Btyp)
10198 and then Present (Non_Limited_View (Des_Btyp))
10199 then
10200 Des_Btyp := Non_Limited_View (Des_Btyp);
10202 elsif Ekind (Des_Btyp) = E_Incomplete_Subtype then
10203 Des_Btyp := Etype (Des_Btyp);
10204 end if;
10205 end if;
10207 if (Attr_Id = Attribute_Access
10208 or else
10209 Attr_Id = Attribute_Unchecked_Access)
10210 and then (Ekind (Btyp) = E_General_Access_Type
10211 or else Ekind (Btyp) = E_Anonymous_Access_Type)
10212 then
10213 -- Ada 2005 (AI-230): Check the accessibility of anonymous
10214 -- access types for stand-alone objects, record and array
10215 -- components, and return objects. For a component definition
10216 -- the level is the same of the enclosing composite type.
10218 if Ada_Version >= Ada_2005
10219 and then (Is_Local_Anonymous_Access (Btyp)
10221 -- Handle cases where Btyp is the anonymous access
10222 -- type of an Ada 2012 stand-alone object.
10224 or else Nkind (Associated_Node_For_Itype (Btyp)) =
10225 N_Object_Declaration)
10226 and then
10227 Object_Access_Level (P) > Deepest_Type_Access_Level (Btyp)
10228 and then Attr_Id = Attribute_Access
10229 then
10230 -- In an instance, this is a runtime check, but one we know
10231 -- will fail, so generate an appropriate warning. As usual,
10232 -- this kind of warning is an error in SPARK mode.
10234 if In_Instance_Body then
10235 Error_Msg_Warn := SPARK_Mode /= On;
10236 Error_Msg_F
10237 ("non-local pointer cannot point to local object<<", P);
10238 Error_Msg_F ("\Program_Error [<<", P);
10240 Rewrite (N,
10241 Make_Raise_Program_Error (Loc,
10242 Reason => PE_Accessibility_Check_Failed));
10243 Set_Etype (N, Typ);
10245 else
10246 Error_Msg_F
10247 ("non-local pointer cannot point to local object", P);
10248 end if;
10249 end if;
10251 if Is_Dependent_Component_Of_Mutable_Object (P) then
10252 Error_Msg_F
10253 ("illegal attribute for discriminant-dependent component",
10255 end if;
10257 -- Check static matching rule of 3.10.2(27). Nominal subtype
10258 -- of the prefix must statically match the designated type.
10260 Nom_Subt := Etype (P);
10262 if Is_Constr_Subt_For_U_Nominal (Nom_Subt) then
10263 Nom_Subt := Base_Type (Nom_Subt);
10264 end if;
10266 if Is_Tagged_Type (Designated_Type (Typ)) then
10268 -- If the attribute is in the context of an access
10269 -- parameter, then the prefix is allowed to be of
10270 -- the class-wide type (by AI-127).
10272 if Ekind (Typ) = E_Anonymous_Access_Type then
10273 if not Covers (Designated_Type (Typ), Nom_Subt)
10274 and then not Covers (Nom_Subt, Designated_Type (Typ))
10275 then
10276 declare
10277 Desig : Entity_Id;
10279 begin
10280 Desig := Designated_Type (Typ);
10282 if Is_Class_Wide_Type (Desig) then
10283 Desig := Etype (Desig);
10284 end if;
10286 if Is_Anonymous_Tagged_Base (Nom_Subt, Desig) then
10287 null;
10289 else
10290 Error_Msg_FE
10291 ("type of prefix: & not compatible",
10292 P, Nom_Subt);
10293 Error_Msg_FE
10294 ("\with &, the expected designated type",
10295 P, Designated_Type (Typ));
10296 end if;
10297 end;
10298 end if;
10300 elsif not Covers (Designated_Type (Typ), Nom_Subt)
10301 or else
10302 (not Is_Class_Wide_Type (Designated_Type (Typ))
10303 and then Is_Class_Wide_Type (Nom_Subt))
10304 then
10305 Error_Msg_FE
10306 ("type of prefix: & is not covered", P, Nom_Subt);
10307 Error_Msg_FE
10308 ("\by &, the expected designated type" &
10309 " (RM 3.10.2 (27))", P, Designated_Type (Typ));
10310 end if;
10312 if Is_Class_Wide_Type (Designated_Type (Typ))
10313 and then Has_Discriminants (Etype (Designated_Type (Typ)))
10314 and then Is_Constrained (Etype (Designated_Type (Typ)))
10315 and then Designated_Type (Typ) /= Nom_Subt
10316 then
10317 Apply_Discriminant_Check
10318 (N, Etype (Designated_Type (Typ)));
10319 end if;
10321 -- Ada 2005 (AI-363): Require static matching when designated
10322 -- type has discriminants and a constrained partial view, since
10323 -- in general objects of such types are mutable, so we can't
10324 -- allow the access value to designate a constrained object
10325 -- (because access values must be assumed to designate mutable
10326 -- objects when designated type does not impose a constraint).
10328 elsif Subtypes_Statically_Match (Des_Btyp, Nom_Subt) then
10329 null;
10331 elsif Has_Discriminants (Designated_Type (Typ))
10332 and then not Is_Constrained (Des_Btyp)
10333 and then
10334 (Ada_Version < Ada_2005
10335 or else
10336 not Object_Type_Has_Constrained_Partial_View
10337 (Typ => Designated_Type (Base_Type (Typ)),
10338 Scop => Current_Scope))
10339 then
10340 null;
10342 else
10343 Error_Msg_F
10344 ("object subtype must statically match "
10345 & "designated subtype", P);
10347 if Is_Entity_Name (P)
10348 and then Is_Array_Type (Designated_Type (Typ))
10349 then
10350 declare
10351 D : constant Node_Id := Declaration_Node (Entity (P));
10352 begin
10353 Error_Msg_N
10354 ("aliased object has explicit bounds??", D);
10355 Error_Msg_N
10356 ("\declare without bounds (and with explicit "
10357 & "initialization)??", D);
10358 Error_Msg_N
10359 ("\for use with unconstrained access??", D);
10360 end;
10361 end if;
10362 end if;
10364 -- Check the static accessibility rule of 3.10.2(28). Note that
10365 -- this check is not performed for the case of an anonymous
10366 -- access type, since the access attribute is always legal
10367 -- in such a context.
10369 if Attr_Id /= Attribute_Unchecked_Access
10370 and then Ekind (Btyp) = E_General_Access_Type
10371 and then
10372 Object_Access_Level (P) > Deepest_Type_Access_Level (Btyp)
10373 then
10374 Accessibility_Message;
10375 return;
10376 end if;
10377 end if;
10379 if Ekind_In (Btyp, E_Access_Protected_Subprogram_Type,
10380 E_Anonymous_Access_Protected_Subprogram_Type)
10381 then
10382 if Is_Entity_Name (P)
10383 and then not Is_Protected_Type (Scope (Entity (P)))
10384 then
10385 Error_Msg_F ("context requires a protected subprogram", P);
10387 -- Check accessibility of protected object against that of the
10388 -- access type, but only on user code, because the expander
10389 -- creates access references for handlers. If the context is an
10390 -- anonymous_access_to_protected, there are no accessibility
10391 -- checks either. Omit check entirely for Unrestricted_Access.
10393 elsif Object_Access_Level (P) > Deepest_Type_Access_Level (Btyp)
10394 and then Comes_From_Source (N)
10395 and then Ekind (Btyp) = E_Access_Protected_Subprogram_Type
10396 and then Attr_Id /= Attribute_Unrestricted_Access
10397 then
10398 Accessibility_Message;
10399 return;
10401 -- AI05-0225: If the context is not an access to protected
10402 -- function, the prefix must be a variable, given that it may
10403 -- be used subsequently in a protected call.
10405 elsif Nkind (P) = N_Selected_Component
10406 and then not Is_Variable (Prefix (P))
10407 and then Ekind (Entity (Selector_Name (P))) /= E_Function
10408 then
10409 Error_Msg_N
10410 ("target object of access to protected procedure "
10411 & "must be variable", N);
10413 elsif Is_Entity_Name (P) then
10414 Check_Internal_Protected_Use (N, Entity (P));
10415 end if;
10417 elsif Ekind_In (Btyp, E_Access_Subprogram_Type,
10418 E_Anonymous_Access_Subprogram_Type)
10419 and then Ekind (Etype (N)) = E_Access_Protected_Subprogram_Type
10420 then
10421 Error_Msg_F ("context requires a non-protected subprogram", P);
10422 end if;
10424 -- The context cannot be a pool-specific type, but this is a
10425 -- legality rule, not a resolution rule, so it must be checked
10426 -- separately, after possibly disambiguation (see AI-245).
10428 if Ekind (Btyp) = E_Access_Type
10429 and then Attr_Id /= Attribute_Unrestricted_Access
10430 then
10431 Wrong_Type (N, Typ);
10432 end if;
10434 -- The context may be a constrained access type (however ill-
10435 -- advised such subtypes might be) so in order to generate a
10436 -- constraint check when needed set the type of the attribute
10437 -- reference to the base type of the context.
10439 Set_Etype (N, Btyp);
10441 -- Check for incorrect atomic/volatile reference (RM C.6(12))
10443 if Attr_Id /= Attribute_Unrestricted_Access then
10444 if Is_Atomic_Object (P)
10445 and then not Is_Atomic (Designated_Type (Typ))
10446 then
10447 Error_Msg_F
10448 ("access to atomic object cannot yield access-to-" &
10449 "non-atomic type", P);
10451 elsif Is_Volatile_Object (P)
10452 and then not Is_Volatile (Designated_Type (Typ))
10453 then
10454 Error_Msg_F
10455 ("access to volatile object cannot yield access-to-" &
10456 "non-volatile type", P);
10457 end if;
10458 end if;
10460 -- Check for unrestricted access where expected type is a thin
10461 -- pointer to an unconstrained array.
10463 if Non_Aliased_Prefix (N)
10464 and then Has_Size_Clause (Typ)
10465 and then RM_Size (Typ) = System_Address_Size
10466 then
10467 declare
10468 DT : constant Entity_Id := Designated_Type (Typ);
10469 begin
10470 if Is_Array_Type (DT) and then not Is_Constrained (DT) then
10471 Error_Msg_N
10472 ("illegal use of Unrestricted_Access attribute", P);
10473 Error_Msg_N
10474 ("\attempt to generate thin pointer to unaliased "
10475 & "object", P);
10476 end if;
10477 end;
10478 end if;
10480 -- Mark that address of entity is taken
10482 if Is_Entity_Name (P) then
10483 Set_Address_Taken (Entity (P));
10484 end if;
10486 -- Deal with possible elaboration check
10488 if Is_Entity_Name (P) and then Is_Subprogram (Entity (P)) then
10489 declare
10490 Subp_Id : constant Entity_Id := Entity (P);
10491 Scop : constant Entity_Id := Scope (Subp_Id);
10492 Subp_Decl : constant Node_Id :=
10493 Unit_Declaration_Node (Subp_Id);
10495 Flag_Id : Entity_Id;
10496 HSS : Node_Id;
10497 Stmt : Node_Id;
10499 -- If the access has been taken and the body of the subprogram
10500 -- has not been see yet, indirect calls must be protected with
10501 -- elaboration checks. We have the proper elaboration machinery
10502 -- for subprograms declared in packages, but within a block or
10503 -- a subprogram the body will appear in the same declarative
10504 -- part, and we must insert a check in the eventual body itself
10505 -- using the elaboration flag that we generate now. The check
10506 -- is then inserted when the body is expanded. This processing
10507 -- is not needed for a stand alone expression function because
10508 -- the internally generated spec and body are always inserted
10509 -- as a pair in the same declarative list.
10511 begin
10512 if Expander_Active
10513 and then Comes_From_Source (Subp_Id)
10514 and then Comes_From_Source (N)
10515 and then In_Open_Scopes (Scop)
10516 and then Ekind_In (Scop, E_Block, E_Procedure, E_Function)
10517 and then not Has_Completion (Subp_Id)
10518 and then No (Elaboration_Entity (Subp_Id))
10519 and then Nkind (Subp_Decl) = N_Subprogram_Declaration
10520 and then Nkind (Original_Node (Subp_Decl)) /=
10521 N_Expression_Function
10522 then
10523 -- Create elaboration variable for it
10525 Flag_Id := Make_Temporary (Loc, 'E');
10526 Set_Elaboration_Entity (Subp_Id, Flag_Id);
10527 Set_Is_Frozen (Flag_Id);
10529 -- Insert declaration for flag after subprogram
10530 -- declaration. Note that attribute reference may
10531 -- appear within a nested scope.
10533 Insert_After_And_Analyze (Subp_Decl,
10534 Make_Object_Declaration (Loc,
10535 Defining_Identifier => Flag_Id,
10536 Object_Definition =>
10537 New_Occurrence_Of (Standard_Short_Integer, Loc),
10538 Expression =>
10539 Make_Integer_Literal (Loc, Uint_0)));
10540 end if;
10542 -- Taking the 'Access of an expression function freezes its
10543 -- expression (RM 13.14 10.3/3). This does not apply to an
10544 -- expression function that acts as a completion because the
10545 -- generated body is immediately analyzed and the expression
10546 -- is automatically frozen.
10548 if Ekind (Subp_Id) = E_Function
10549 and then Nkind (Subp_Decl) = N_Subprogram_Declaration
10550 and then Nkind (Original_Node (Subp_Decl)) =
10551 N_Expression_Function
10552 and then Present (Corresponding_Body (Subp_Decl))
10553 and then not Analyzed (Corresponding_Body (Subp_Decl))
10554 then
10555 HSS :=
10556 Handled_Statement_Sequence
10557 (Unit_Declaration_Node
10558 (Corresponding_Body (Subp_Decl)));
10560 if Present (HSS) then
10561 Stmt := First (Statements (HSS));
10563 if Nkind (Stmt) = N_Simple_Return_Statement then
10564 Freeze_Expression (Expression (Stmt));
10565 end if;
10566 end if;
10567 end if;
10568 end;
10569 end if;
10570 end Access_Attribute;
10572 -------------
10573 -- Address --
10574 -------------
10576 -- Deal with resolving the type for Address attribute, overloading
10577 -- is not permitted here, since there is no context to resolve it.
10579 when Attribute_Address | Attribute_Code_Address =>
10580 Address_Attribute : begin
10582 -- To be safe, assume that if the address of a variable is taken,
10583 -- it may be modified via this address, so note modification.
10585 if Is_Variable (P) then
10586 Note_Possible_Modification (P, Sure => False);
10587 end if;
10589 if Nkind (P) in N_Subexpr
10590 and then Is_Overloaded (P)
10591 then
10592 Get_First_Interp (P, Index, It);
10593 Get_Next_Interp (Index, It);
10595 if Present (It.Nam) then
10596 Error_Msg_Name_1 := Aname;
10597 Error_Msg_F
10598 ("prefix of % attribute cannot be overloaded", P);
10599 end if;
10600 end if;
10602 if not Is_Entity_Name (P)
10603 or else not Is_Overloadable (Entity (P))
10604 then
10605 if not Is_Task_Type (Etype (P))
10606 or else Nkind (P) = N_Explicit_Dereference
10607 then
10608 Resolve (P);
10609 end if;
10610 end if;
10612 -- If this is the name of a derived subprogram, or that of a
10613 -- generic actual, the address is that of the original entity.
10615 if Is_Entity_Name (P)
10616 and then Is_Overloadable (Entity (P))
10617 and then Present (Alias (Entity (P)))
10618 then
10619 Rewrite (P,
10620 New_Occurrence_Of (Alias (Entity (P)), Sloc (P)));
10621 end if;
10623 if Is_Entity_Name (P) then
10624 Set_Address_Taken (Entity (P));
10625 end if;
10627 if Nkind (P) = N_Slice then
10629 -- Arr (X .. Y)'address is identical to Arr (X)'address,
10630 -- even if the array is packed and the slice itself is not
10631 -- addressable. Transform the prefix into an indexed component.
10633 -- Note that the transformation is safe only if we know that
10634 -- the slice is non-null. That is because a null slice can have
10635 -- an out of bounds index value.
10637 -- Right now, gigi blows up if given 'Address on a slice as a
10638 -- result of some incorrect freeze nodes generated by the front
10639 -- end, and this covers up that bug in one case, but the bug is
10640 -- likely still there in the cases not handled by this code ???
10642 -- It's not clear what 'Address *should* return for a null
10643 -- slice with out of bounds indexes, this might be worth an ARG
10644 -- discussion ???
10646 -- One approach would be to do a length check unconditionally,
10647 -- and then do the transformation below unconditionally, but
10648 -- analyze with checks off, avoiding the problem of the out of
10649 -- bounds index. This approach would interpret the address of
10650 -- an out of bounds null slice as being the address where the
10651 -- array element would be if there was one, which is probably
10652 -- as reasonable an interpretation as any ???
10654 declare
10655 Loc : constant Source_Ptr := Sloc (P);
10656 D : constant Node_Id := Discrete_Range (P);
10657 Lo : Node_Id;
10659 begin
10660 if Is_Entity_Name (D)
10661 and then
10662 Not_Null_Range
10663 (Type_Low_Bound (Entity (D)),
10664 Type_High_Bound (Entity (D)))
10665 then
10666 Lo :=
10667 Make_Attribute_Reference (Loc,
10668 Prefix => (New_Occurrence_Of (Entity (D), Loc)),
10669 Attribute_Name => Name_First);
10671 elsif Nkind (D) = N_Range
10672 and then Not_Null_Range (Low_Bound (D), High_Bound (D))
10673 then
10674 Lo := Low_Bound (D);
10676 else
10677 Lo := Empty;
10678 end if;
10680 if Present (Lo) then
10681 Rewrite (P,
10682 Make_Indexed_Component (Loc,
10683 Prefix => Relocate_Node (Prefix (P)),
10684 Expressions => New_List (Lo)));
10686 Analyze_And_Resolve (P);
10687 end if;
10688 end;
10689 end if;
10690 end Address_Attribute;
10692 ------------------
10693 -- Body_Version --
10694 ------------------
10696 -- Prefix of Body_Version attribute can be a subprogram name which
10697 -- must not be resolved, since this is not a call.
10699 when Attribute_Body_Version =>
10700 null;
10702 ------------
10703 -- Caller --
10704 ------------
10706 -- Prefix of Caller attribute is an entry name which must not
10707 -- be resolved, since this is definitely not an entry call.
10709 when Attribute_Caller =>
10710 null;
10712 ------------------
10713 -- Code_Address --
10714 ------------------
10716 -- Shares processing with Address attribute
10718 -----------
10719 -- Count --
10720 -----------
10722 -- If the prefix of the Count attribute is an entry name it must not
10723 -- be resolved, since this is definitely not an entry call. However,
10724 -- if it is an element of an entry family, the index itself may
10725 -- have to be resolved because it can be a general expression.
10727 when Attribute_Count =>
10728 if Nkind (P) = N_Indexed_Component
10729 and then Is_Entity_Name (Prefix (P))
10730 then
10731 declare
10732 Indx : constant Node_Id := First (Expressions (P));
10733 Fam : constant Entity_Id := Entity (Prefix (P));
10734 begin
10735 Resolve (Indx, Entry_Index_Type (Fam));
10736 Apply_Range_Check (Indx, Entry_Index_Type (Fam));
10737 end;
10738 end if;
10740 ----------------
10741 -- Elaborated --
10742 ----------------
10744 -- Prefix of the Elaborated attribute is a subprogram name which
10745 -- must not be resolved, since this is definitely not a call. Note
10746 -- that it is a library unit, so it cannot be overloaded here.
10748 when Attribute_Elaborated =>
10749 null;
10751 -------------
10752 -- Enabled --
10753 -------------
10755 -- Prefix of Enabled attribute is a check name, which must be treated
10756 -- specially and not touched by Resolve.
10758 when Attribute_Enabled =>
10759 null;
10761 ----------------
10762 -- Loop_Entry --
10763 ----------------
10765 -- Do not resolve the prefix of Loop_Entry, instead wait until the
10766 -- attribute has been expanded (see Expand_Loop_Entry_Attributes).
10767 -- The delay ensures that any generated checks or temporaries are
10768 -- inserted before the relocated prefix.
10770 when Attribute_Loop_Entry =>
10771 null;
10773 --------------------
10774 -- Mechanism_Code --
10775 --------------------
10777 -- Prefix of the Mechanism_Code attribute is a function name
10778 -- which must not be resolved. Should we check for overloaded ???
10780 when Attribute_Mechanism_Code =>
10781 null;
10783 ------------------
10784 -- Partition_ID --
10785 ------------------
10787 -- Most processing is done in sem_dist, after determining the
10788 -- context type. Node is rewritten as a conversion to a runtime call.
10790 when Attribute_Partition_ID =>
10791 Process_Partition_Id (N);
10792 return;
10794 ------------------
10795 -- Pool_Address --
10796 ------------------
10798 when Attribute_Pool_Address =>
10799 Resolve (P);
10801 -----------
10802 -- Range --
10803 -----------
10805 -- We replace the Range attribute node with a range expression whose
10806 -- bounds are the 'First and 'Last attributes applied to the same
10807 -- prefix. The reason that we do this transformation here instead of
10808 -- in the expander is that it simplifies other parts of the semantic
10809 -- analysis which assume that the Range has been replaced; thus it
10810 -- must be done even when in semantic-only mode (note that the RM
10811 -- specifically mentions this equivalence, we take care that the
10812 -- prefix is only evaluated once).
10814 when Attribute_Range => Range_Attribute :
10815 declare
10816 LB : Node_Id;
10817 HB : Node_Id;
10818 Dims : List_Id;
10820 begin
10821 if not Is_Entity_Name (P)
10822 or else not Is_Type (Entity (P))
10823 then
10824 Resolve (P);
10825 end if;
10827 Dims := Expressions (N);
10829 HB :=
10830 Make_Attribute_Reference (Loc,
10831 Prefix => Duplicate_Subexpr (P, Name_Req => True),
10832 Attribute_Name => Name_Last,
10833 Expressions => Dims);
10835 LB :=
10836 Make_Attribute_Reference (Loc,
10837 Prefix => P,
10838 Attribute_Name => Name_First,
10839 Expressions => (Dims));
10841 -- Do not share the dimension indicator, if present. Even
10842 -- though it is a static constant, its source location
10843 -- may be modified when printing expanded code and node
10844 -- sharing will lead to chaos in Sprint.
10846 if Present (Dims) then
10847 Set_Expressions (LB,
10848 New_List (New_Copy_Tree (First (Dims))));
10849 end if;
10851 -- If the original was marked as Must_Not_Freeze (see code
10852 -- in Sem_Ch3.Make_Index), then make sure the rewriting
10853 -- does not freeze either.
10855 if Must_Not_Freeze (N) then
10856 Set_Must_Not_Freeze (HB);
10857 Set_Must_Not_Freeze (LB);
10858 Set_Must_Not_Freeze (Prefix (HB));
10859 Set_Must_Not_Freeze (Prefix (LB));
10860 end if;
10862 if Raises_Constraint_Error (Prefix (N)) then
10864 -- Preserve Sloc of prefix in the new bounds, so that
10865 -- the posted warning can be removed if we are within
10866 -- unreachable code.
10868 Set_Sloc (LB, Sloc (Prefix (N)));
10869 Set_Sloc (HB, Sloc (Prefix (N)));
10870 end if;
10872 Rewrite (N, Make_Range (Loc, LB, HB));
10873 Analyze_And_Resolve (N, Typ);
10875 -- Ensure that the expanded range does not have side effects
10877 Force_Evaluation (LB);
10878 Force_Evaluation (HB);
10880 -- Normally after resolving attribute nodes, Eval_Attribute
10881 -- is called to do any possible static evaluation of the node.
10882 -- However, here since the Range attribute has just been
10883 -- transformed into a range expression it is no longer an
10884 -- attribute node and therefore the call needs to be avoided
10885 -- and is accomplished by simply returning from the procedure.
10887 return;
10888 end Range_Attribute;
10890 ------------
10891 -- Result --
10892 ------------
10894 -- We will only come here during the prescan of a spec expression
10895 -- containing a Result attribute. In that case the proper Etype has
10896 -- already been set, and nothing more needs to be done here.
10898 when Attribute_Result =>
10899 null;
10901 -----------------
10902 -- UET_Address --
10903 -----------------
10905 -- Prefix must not be resolved in this case, since it is not a
10906 -- real entity reference. No action of any kind is require.
10908 when Attribute_UET_Address =>
10909 return;
10911 ----------------------
10912 -- Unchecked_Access --
10913 ----------------------
10915 -- Processing is shared with Access
10917 -------------------------
10918 -- Unrestricted_Access --
10919 -------------------------
10921 -- Processing is shared with Access
10923 ------------
10924 -- Update --
10925 ------------
10927 -- Resolve aggregate components in component associations
10929 when Attribute_Update =>
10930 declare
10931 Aggr : constant Node_Id := First (Expressions (N));
10932 Typ : constant Entity_Id := Etype (Prefix (N));
10933 Assoc : Node_Id;
10934 Comp : Node_Id;
10935 Expr : Node_Id;
10937 begin
10938 -- Set the Etype of the aggregate to that of the prefix, even
10939 -- though the aggregate may not be a proper representation of a
10940 -- value of the type (missing or duplicated associations, etc.)
10941 -- Complete resolution of the prefix. Note that in Ada 2012 it
10942 -- can be a qualified expression that is e.g. an aggregate.
10944 Set_Etype (Aggr, Typ);
10945 Resolve (Prefix (N), Typ);
10947 -- For an array type, resolve expressions with the component
10948 -- type of the array, and apply constraint checks when needed.
10950 if Is_Array_Type (Typ) then
10951 Assoc := First (Component_Associations (Aggr));
10952 while Present (Assoc) loop
10953 Expr := Expression (Assoc);
10954 Resolve (Expr, Component_Type (Typ));
10956 -- For scalar array components set Do_Range_Check when
10957 -- needed. Constraint checking on non-scalar components
10958 -- is done in Aggregate_Constraint_Checks, but only if
10959 -- full analysis is enabled. These flags are not set in
10960 -- the front-end in GnatProve mode.
10962 if Is_Scalar_Type (Component_Type (Typ))
10963 and then not Is_OK_Static_Expression (Expr)
10964 then
10965 if Is_Entity_Name (Expr)
10966 and then Etype (Expr) = Component_Type (Typ)
10967 then
10968 null;
10970 else
10971 Set_Do_Range_Check (Expr);
10972 end if;
10973 end if;
10975 -- The choices in the association are static constants,
10976 -- or static aggregates each of whose components belongs
10977 -- to the proper index type. However, they must also
10978 -- belong to the index subtype (s) of the prefix, which
10979 -- may be a subtype (e.g. given by a slice).
10981 -- Choices may also be identifiers with no staticness
10982 -- requirements, in which case they must resolve to the
10983 -- index type.
10985 declare
10986 C : Node_Id;
10987 C_E : Node_Id;
10988 Indx : Node_Id;
10990 begin
10991 C := First (Choices (Assoc));
10992 while Present (C) loop
10993 Indx := First_Index (Etype (Prefix (N)));
10995 if Nkind (C) /= N_Aggregate then
10996 Analyze_And_Resolve (C, Etype (Indx));
10997 Apply_Constraint_Check (C, Etype (Indx));
10998 Check_Non_Static_Context (C);
11000 else
11001 C_E := First (Expressions (C));
11002 while Present (C_E) loop
11003 Analyze_And_Resolve (C_E, Etype (Indx));
11004 Apply_Constraint_Check (C_E, Etype (Indx));
11005 Check_Non_Static_Context (C_E);
11007 Next (C_E);
11008 Next_Index (Indx);
11009 end loop;
11010 end if;
11012 Next (C);
11013 end loop;
11014 end;
11016 Next (Assoc);
11017 end loop;
11019 -- For a record type, use type of each component, which is
11020 -- recorded during analysis.
11022 else
11023 Assoc := First (Component_Associations (Aggr));
11024 while Present (Assoc) loop
11025 Comp := First (Choices (Assoc));
11027 if Nkind (Comp) /= N_Others_Choice
11028 and then not Error_Posted (Comp)
11029 then
11030 Resolve (Expression (Assoc), Etype (Entity (Comp)));
11031 end if;
11033 Next (Assoc);
11034 end loop;
11035 end if;
11036 end;
11038 ---------
11039 -- Val --
11040 ---------
11042 -- Apply range check. Note that we did not do this during the
11043 -- analysis phase, since we wanted Eval_Attribute to have a
11044 -- chance at finding an illegal out of range value.
11046 when Attribute_Val =>
11048 -- Note that we do our own Eval_Attribute call here rather than
11049 -- use the common one, because we need to do processing after
11050 -- the call, as per above comment.
11052 Eval_Attribute (N);
11054 -- Eval_Attribute may replace the node with a raise CE, or
11055 -- fold it to a constant. Obviously we only apply a scalar
11056 -- range check if this did not happen.
11058 if Nkind (N) = N_Attribute_Reference
11059 and then Attribute_Name (N) = Name_Val
11060 then
11061 Apply_Scalar_Range_Check (First (Expressions (N)), Btyp);
11062 end if;
11064 return;
11066 -------------
11067 -- Version --
11068 -------------
11070 -- Prefix of Version attribute can be a subprogram name which
11071 -- must not be resolved, since this is not a call.
11073 when Attribute_Version =>
11074 null;
11076 ----------------------
11077 -- Other Attributes --
11078 ----------------------
11080 -- For other attributes, resolve prefix unless it is a type. If
11081 -- the attribute reference itself is a type name ('Base and 'Class)
11082 -- then this is only legal within a task or protected record.
11084 when others =>
11085 if not Is_Entity_Name (P) or else not Is_Type (Entity (P)) then
11086 Resolve (P);
11087 end if;
11089 -- If the attribute reference itself is a type name ('Base,
11090 -- 'Class) then this is only legal within a task or protected
11091 -- record. What is this all about ???
11093 if Is_Entity_Name (N) and then Is_Type (Entity (N)) then
11094 if Is_Concurrent_Type (Entity (N))
11095 and then In_Open_Scopes (Entity (P))
11096 then
11097 null;
11098 else
11099 Error_Msg_N
11100 ("invalid use of subtype name in expression or call", N);
11101 end if;
11102 end if;
11104 -- For attributes whose argument may be a string, complete
11105 -- resolution of argument now. This avoids premature expansion
11106 -- (and the creation of transient scopes) before the attribute
11107 -- reference is resolved.
11109 case Attr_Id is
11110 when Attribute_Value =>
11111 Resolve (First (Expressions (N)), Standard_String);
11113 when Attribute_Wide_Value =>
11114 Resolve (First (Expressions (N)), Standard_Wide_String);
11116 when Attribute_Wide_Wide_Value =>
11117 Resolve (First (Expressions (N)), Standard_Wide_Wide_String);
11119 when others => null;
11120 end case;
11122 -- If the prefix of the attribute is a class-wide type then it
11123 -- will be expanded into a dispatching call to a predefined
11124 -- primitive. Therefore we must check for potential violation
11125 -- of such restriction.
11127 if Is_Class_Wide_Type (Etype (P)) then
11128 Check_Restriction (No_Dispatching_Calls, N);
11129 end if;
11130 end case;
11132 -- Normally the Freezing is done by Resolve but sometimes the Prefix
11133 -- is not resolved, in which case the freezing must be done now.
11135 Freeze_Expression (P);
11137 -- Finally perform static evaluation on the attribute reference
11139 Analyze_Dimension (N);
11140 Eval_Attribute (N);
11141 end Resolve_Attribute;
11143 ------------------------
11144 -- Set_Boolean_Result --
11145 ------------------------
11147 procedure Set_Boolean_Result (N : Node_Id; B : Boolean) is
11148 Loc : constant Source_Ptr := Sloc (N);
11149 begin
11150 if B then
11151 Rewrite (N, New_Occurrence_Of (Standard_True, Loc));
11152 else
11153 Rewrite (N, New_Occurrence_Of (Standard_False, Loc));
11154 end if;
11155 end Set_Boolean_Result;
11157 --------------------------------
11158 -- Stream_Attribute_Available --
11159 --------------------------------
11161 function Stream_Attribute_Available
11162 (Typ : Entity_Id;
11163 Nam : TSS_Name_Type;
11164 Partial_View : Node_Id := Empty) return Boolean
11166 Etyp : Entity_Id := Typ;
11168 -- Start of processing for Stream_Attribute_Available
11170 begin
11171 -- We need some comments in this body ???
11173 if Has_Stream_Attribute_Definition (Typ, Nam) then
11174 return True;
11175 end if;
11177 if Is_Class_Wide_Type (Typ) then
11178 return not Is_Limited_Type (Typ)
11179 or else Stream_Attribute_Available (Etype (Typ), Nam);
11180 end if;
11182 if Nam = TSS_Stream_Input
11183 and then Is_Abstract_Type (Typ)
11184 and then not Is_Class_Wide_Type (Typ)
11185 then
11186 return False;
11187 end if;
11189 if not (Is_Limited_Type (Typ)
11190 or else (Present (Partial_View)
11191 and then Is_Limited_Type (Partial_View)))
11192 then
11193 return True;
11194 end if;
11196 -- In Ada 2005, Input can invoke Read, and Output can invoke Write
11198 if Nam = TSS_Stream_Input
11199 and then Ada_Version >= Ada_2005
11200 and then Stream_Attribute_Available (Etyp, TSS_Stream_Read)
11201 then
11202 return True;
11204 elsif Nam = TSS_Stream_Output
11205 and then Ada_Version >= Ada_2005
11206 and then Stream_Attribute_Available (Etyp, TSS_Stream_Write)
11207 then
11208 return True;
11209 end if;
11211 -- Case of Read and Write: check for attribute definition clause that
11212 -- applies to an ancestor type.
11214 while Etype (Etyp) /= Etyp loop
11215 Etyp := Etype (Etyp);
11217 if Has_Stream_Attribute_Definition (Etyp, Nam) then
11218 return True;
11219 end if;
11220 end loop;
11222 if Ada_Version < Ada_2005 then
11224 -- In Ada 95 mode, also consider a non-visible definition
11226 declare
11227 Btyp : constant Entity_Id := Implementation_Base_Type (Typ);
11228 begin
11229 return Btyp /= Typ
11230 and then Stream_Attribute_Available
11231 (Btyp, Nam, Partial_View => Typ);
11232 end;
11233 end if;
11235 return False;
11236 end Stream_Attribute_Available;
11238 end Sem_Attr;