1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2014, Free Software Foundation, Inc. --
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. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
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
;
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
;
43 with Lib
.Xref
; use Lib
.Xref
;
44 with Nlists
; use Nlists
;
45 with Nmake
; use Nmake
;
47 with Restrict
; use Restrict
;
48 with Rident
; use Rident
;
49 with Rtsfind
; use Rtsfind
;
50 with Sdefault
; use Sdefault
;
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 Stringt
; use Stringt
;
70 with Stylesw
; use Stylesw
;
71 with Targparm
; use Targparm
;
72 with Ttypes
; use Ttypes
;
73 with Tbuild
; use Tbuild
;
74 with Uintp
; use Uintp
;
75 with Uname
; use Uname
;
76 with Urealp
; use Urealp
;
78 package body Sem_Attr
is
80 True_Value
: constant Uint
:= Uint_1
;
81 False_Value
: constant Uint
:= Uint_0
;
82 -- Synonyms to be used when these constants are used as Boolean values
84 Bad_Attribute
: exception;
85 -- Exception raised if an error is detected during attribute processing,
86 -- used so that we can abandon the processing so we don't run into
87 -- trouble with cascaded errors.
89 -- The following array is the list of attributes defined in the Ada 83 RM.
90 -- In Ada 83 mode, these are the only recognized attributes. In other Ada
91 -- modes all these attributes are recognized, even if removed in Ada 95.
93 Attribute_83
: constant Attribute_Class_Array
:= Attribute_Class_Array
'(
99 Attribute_Constrained |
106 Attribute_First_Bit |
112 Attribute_Leading_Part |
114 Attribute_Machine_Emax |
115 Attribute_Machine_Emin |
116 Attribute_Machine_Mantissa |
117 Attribute_Machine_Overflows |
118 Attribute_Machine_Radix |
119 Attribute_Machine_Rounds |
125 Attribute_Safe_Emax |
126 Attribute_Safe_Large |
127 Attribute_Safe_Small |
130 Attribute_Storage_Size |
132 Attribute_Terminated |
135 Attribute_Width => True,
138 -- The following array is the list of attributes defined in the Ada 2005
139 -- RM which are not defined in Ada 95. These are recognized in Ada 95 mode,
140 -- but in Ada 95 they are considered to be implementation defined.
142 Attribute_05 : constant Attribute_Class_Array := Attribute_Class_Array'(
143 Attribute_Machine_Rounding |
146 Attribute_Stream_Size |
147 Attribute_Wide_Wide_Width
=> True,
150 -- The following array is the list of attributes defined in the Ada 2012
151 -- RM which are not defined in Ada 2005. These are recognized in Ada 95
152 -- and Ada 2005 modes, but are considered to be implementation defined.
154 Attribute_12
: constant Attribute_Class_Array
:= Attribute_Class_Array
'(
155 Attribute_First_Valid |
156 Attribute_Has_Same_Storage |
157 Attribute_Last_Valid |
158 Attribute_Max_Alignment_For_Allocation => True,
161 -- The following array contains all attributes that imply a modification
162 -- of their prefixes or result in an access value. Such prefixes can be
163 -- considered as lvalues.
165 Attribute_Name_Implies_Lvalue_Prefix : constant Attribute_Class_Array :=
166 Attribute_Class_Array'(
171 Attribute_Unchecked_Access |
172 Attribute_Unrestricted_Access
=> True,
175 -----------------------
176 -- Local_Subprograms --
177 -----------------------
179 procedure Eval_Attribute
(N
: Node_Id
);
180 -- Performs compile time evaluation of attributes where possible, leaving
181 -- the Is_Static_Expression/Raises_Constraint_Error flags appropriately
182 -- set, and replacing the node with a literal node if the value can be
183 -- computed at compile time. All static attribute references are folded,
184 -- as well as a number of cases of non-static attributes that can always
185 -- be computed at compile time (e.g. floating-point model attributes that
186 -- are applied to non-static subtypes). Of course in such cases, the
187 -- Is_Static_Expression flag will not be set on the resulting literal.
188 -- Note that the only required action of this procedure is to catch the
189 -- static expression cases as described in the RM. Folding of other cases
190 -- is done where convenient, but some additional non-static folding is in
191 -- Expand_N_Attribute_Reference in cases where this is more convenient.
193 function Is_Anonymous_Tagged_Base
195 Typ
: Entity_Id
) return Boolean;
196 -- For derived tagged types that constrain parent discriminants we build
197 -- an anonymous unconstrained base type. We need to recognize the relation
198 -- between the two when analyzing an access attribute for a constrained
199 -- component, before the full declaration for Typ has been analyzed, and
200 -- where therefore the prefix of the attribute does not match the enclosing
203 procedure Set_Boolean_Result
(N
: Node_Id
; B
: Boolean);
204 -- Rewrites node N with an occurrence of either Standard_False or
205 -- Standard_True, depending on the value of the parameter B. The
206 -- result is marked as a static expression.
208 -----------------------
209 -- Analyze_Attribute --
210 -----------------------
212 procedure Analyze_Attribute
(N
: Node_Id
) is
213 Loc
: constant Source_Ptr
:= Sloc
(N
);
214 Aname
: constant Name_Id
:= Attribute_Name
(N
);
215 P
: constant Node_Id
:= Prefix
(N
);
216 Exprs
: constant List_Id
:= Expressions
(N
);
217 Attr_Id
: constant Attribute_Id
:= Get_Attribute_Id
(Aname
);
222 -- Type of prefix after analysis
224 P_Base_Type
: Entity_Id
;
225 -- Base type of prefix after analysis
227 -----------------------
228 -- Local Subprograms --
229 -----------------------
231 procedure Address_Checks
;
232 -- Semantic checks for valid use of Address attribute. This was made
233 -- a separate routine with the idea of using it for unrestricted access
234 -- which seems like it should follow the same rules, but that turned
235 -- out to be impractical. So now this is only used for Address.
237 procedure Analyze_Access_Attribute
;
238 -- Used for Access, Unchecked_Access, Unrestricted_Access attributes.
239 -- Internally, Id distinguishes which of the three cases is involved.
241 procedure Bad_Attribute_For_Predicate
;
242 -- Output error message for use of a predicate (First, Last, Range) not
243 -- allowed with a type that has predicates. If the type is a generic
244 -- actual, then the message is a warning, and we generate code to raise
245 -- program error with an appropriate reason. No error message is given
246 -- for internally generated uses of the attributes. This legality rule
247 -- only applies to scalar types.
249 procedure Check_Array_Or_Scalar_Type
;
250 -- Common procedure used by First, Last, Range attribute to check
251 -- that the prefix is a constrained array or scalar type, or a name
252 -- of an array object, and that an argument appears only if appropriate
253 -- (i.e. only in the array case).
255 procedure Check_Array_Type
;
256 -- Common semantic checks for all array attributes. Checks that the
257 -- prefix is a constrained array type or the name of an array object.
258 -- The error message for non-arrays is specialized appropriately.
260 procedure Check_Asm_Attribute
;
261 -- Common semantic checks for Asm_Input and Asm_Output attributes
263 procedure Check_Component
;
264 -- Common processing for Bit_Position, First_Bit, Last_Bit, and
265 -- Position. Checks prefix is an appropriate selected component.
267 procedure Check_Decimal_Fixed_Point_Type
;
268 -- Check that prefix of attribute N is a decimal fixed-point type
270 procedure Check_Dereference
;
271 -- If the prefix of attribute is an object of an access type, then
272 -- introduce an explicit dereference, and adjust P_Type accordingly.
274 procedure Check_Discrete_Type
;
275 -- Verify that prefix of attribute N is a discrete type
278 -- Check that no attribute arguments are present
280 procedure Check_Either_E0_Or_E1
;
281 -- Check that there are zero or one attribute arguments present
284 -- Check that exactly one attribute argument is present
287 -- Check that two attribute arguments are present
289 procedure Check_Enum_Image
;
290 -- If the prefix type is an enumeration type, set all its literals
291 -- as referenced, since the image function could possibly end up
292 -- referencing any of the literals indirectly. Same for Enum_Val.
293 -- Set the flag only if the reference is in the main code unit. Same
294 -- restriction when resolving 'Value; otherwise an improperly set
295 -- reference when analyzing an inlined body will lose a proper warning
296 -- on a useless with_clause.
298 procedure Check_First_Last_Valid
;
299 -- Perform all checks for First_Valid and Last_Valid attributes
301 procedure Check_Fixed_Point_Type
;
302 -- Verify that prefix of attribute N is a fixed type
304 procedure Check_Fixed_Point_Type_0
;
305 -- Verify that prefix of attribute N is a fixed type and that
306 -- no attribute expressions are present
308 procedure Check_Floating_Point_Type
;
309 -- Verify that prefix of attribute N is a float type
311 procedure Check_Floating_Point_Type_0
;
312 -- Verify that prefix of attribute N is a float type and that
313 -- no attribute expressions are present
315 procedure Check_Floating_Point_Type_1
;
316 -- Verify that prefix of attribute N is a float type and that
317 -- exactly one attribute expression is present
319 procedure Check_Floating_Point_Type_2
;
320 -- Verify that prefix of attribute N is a float type and that
321 -- two attribute expressions are present
323 procedure Check_SPARK_Restriction_On_Attribute
;
324 -- Issue an error in formal mode because attribute N is allowed
326 procedure Check_Integer_Type
;
327 -- Verify that prefix of attribute N is an integer type
329 procedure Check_Modular_Integer_Type
;
330 -- Verify that prefix of attribute N is a modular integer type
332 procedure Check_Not_CPP_Type
;
333 -- Check that P (the prefix of the attribute) is not an CPP type
334 -- for which no Ada predefined primitive is available.
336 procedure Check_Not_Incomplete_Type
;
337 -- Check that P (the prefix of the attribute) is not an incomplete
338 -- type or a private type for which no full view has been given.
340 procedure Check_Object_Reference
(P
: Node_Id
);
341 -- Check that P is an object reference
343 procedure Check_Program_Unit
;
344 -- Verify that prefix of attribute N is a program unit
346 procedure Check_Real_Type
;
347 -- Verify that prefix of attribute N is fixed or float type
349 procedure Check_Scalar_Type
;
350 -- Verify that prefix of attribute N is a scalar type
352 procedure Check_Standard_Prefix
;
353 -- Verify that prefix of attribute N is package Standard. Also checks
354 -- that there are no arguments.
356 procedure Check_Stream_Attribute
(Nam
: TSS_Name_Type
);
357 -- Validity checking for stream attribute. Nam is the TSS name of the
358 -- corresponding possible defined attribute function (e.g. for the
359 -- Read attribute, Nam will be TSS_Stream_Read).
361 procedure Check_System_Prefix
;
362 -- Verify that prefix of attribute N is package System
364 procedure Check_PolyORB_Attribute
;
365 -- Validity checking for PolyORB/DSA attribute
367 procedure Check_Task_Prefix
;
368 -- Verify that prefix of attribute N is a task or task type
370 procedure Check_Type
;
371 -- Verify that the prefix of attribute N is a type
373 procedure Check_Unit_Name
(Nod
: Node_Id
);
374 -- Check that Nod is of the form of a library unit name, i.e that
375 -- it is an identifier, or a selected component whose prefix is
376 -- itself of the form of a library unit name. Note that this is
377 -- quite different from Check_Program_Unit, since it only checks
378 -- the syntactic form of the name, not the semantic identity. This
379 -- is because it is used with attributes (Elab_Body, Elab_Spec,
380 -- UET_Address and Elaborated) which can refer to non-visible unit.
382 procedure Error_Attr
(Msg
: String; Error_Node
: Node_Id
);
383 pragma No_Return
(Error_Attr
);
384 procedure Error_Attr
;
385 pragma No_Return
(Error_Attr
);
386 -- Posts error using Error_Msg_N at given node, sets type of attribute
387 -- node to Any_Type, and then raises Bad_Attribute to avoid any further
388 -- semantic processing. The message typically contains a % insertion
389 -- character which is replaced by the attribute name. The call with
390 -- no arguments is used when the caller has already generated the
391 -- required error messages.
393 procedure Error_Attr_P
(Msg
: String);
394 pragma No_Return
(Error_Attr
);
395 -- Like Error_Attr, but error is posted at the start of the prefix
397 function In_Refined_Post
return Boolean;
398 -- Determine whether the current attribute appears in pragma
401 procedure Legal_Formal_Attribute
;
402 -- Common processing for attributes Definite and Has_Discriminants.
403 -- Checks that prefix is generic indefinite formal type.
405 procedure Max_Alignment_For_Allocation_Max_Size_In_Storage_Elements
;
406 -- Common processing for attributes Max_Alignment_For_Allocation and
407 -- Max_Size_In_Storage_Elements.
410 -- Common processing for attributes Max and Min
412 procedure Standard_Attribute
(Val
: Int
);
413 -- Used to process attributes whose prefix is package Standard which
414 -- yield values of type Universal_Integer. The attribute reference
415 -- node is rewritten with an integer literal of the given value which
416 -- is marked as static.
418 procedure Uneval_Old_Msg
;
419 -- Called when Loop_Entry or Old is used in a potentially unevaluated
420 -- expression. Generates appropriate message or warning depending on
421 -- the setting of Opt.Uneval_Old (or flags in an N_Aspect_Specification
422 -- node in the aspect case).
424 procedure Unexpected_Argument
(En
: Node_Id
);
425 -- Signal unexpected attribute argument (En is the argument)
427 procedure Validate_Non_Static_Attribute_Function_Call
;
428 -- Called when processing an attribute that is a function call to a
429 -- non-static function, i.e. an attribute function that either takes
430 -- non-scalar arguments or returns a non-scalar result. Verifies that
431 -- such a call does not appear in a preelaborable context.
437 procedure Address_Checks
is
439 -- An Address attribute created by expansion is legal even when it
440 -- applies to other entity-denoting expressions.
442 if not Comes_From_Source
(N
) then
445 -- Address attribute on a protected object self reference is legal
447 elsif Is_Protected_Self_Reference
(P
) then
450 -- Address applied to an entity
452 elsif Is_Entity_Name
(P
) then
454 Ent
: constant Entity_Id
:= Entity
(P
);
457 if Is_Subprogram
(Ent
) then
458 Set_Address_Taken
(Ent
);
459 Kill_Current_Values
(Ent
);
461 -- An Address attribute is accepted when generated by the
462 -- compiler for dispatching operation, and an error is
463 -- issued once the subprogram is frozen (to avoid confusing
464 -- errors about implicit uses of Address in the dispatch
465 -- table initialization).
467 if Has_Pragma_Inline_Always
(Entity
(P
))
468 and then Comes_From_Source
(P
)
471 ("prefix of % attribute cannot be Inline_Always "
474 -- It is illegal to apply 'Address to an intrinsic
475 -- subprogram. This is now formalized in AI05-0095.
476 -- In an instance, an attempt to obtain 'Address of an
477 -- intrinsic subprogram (e.g the renaming of a predefined
478 -- operator that is an actual) raises Program_Error.
480 elsif Convention
(Ent
) = Convention_Intrinsic
then
483 Make_Raise_Program_Error
(Loc
,
484 Reason
=> PE_Address_Of_Intrinsic
));
487 Error_Msg_Name_1
:= Aname
;
489 ("cannot take % of intrinsic subprogram", N
);
492 -- Issue an error if prefix denotes an eliminated subprogram
495 Check_For_Eliminated_Subprogram
(P
, Ent
);
498 -- Object or label reference
500 elsif Is_Object
(Ent
) or else Ekind
(Ent
) = E_Label
then
501 Set_Address_Taken
(Ent
);
503 -- Deal with No_Implicit_Aliasing restriction
505 if Restriction_Check_Required
(No_Implicit_Aliasing
) then
506 if not Is_Aliased_View
(P
) then
507 Check_Restriction
(No_Implicit_Aliasing
, P
);
509 Check_No_Implicit_Aliasing
(P
);
513 -- If we have an address of an object, and the attribute
514 -- comes from source, then set the object as potentially
515 -- source modified. We do this because the resulting address
516 -- can potentially be used to modify the variable and we
517 -- might not detect this, leading to some junk warnings.
519 Set_Never_Set_In_Source
(Ent
, False);
521 -- Allow Address to be applied to task or protected type,
522 -- returning null address (what is that about???)
524 elsif (Is_Concurrent_Type
(Etype
(Ent
))
525 and then Etype
(Ent
) = Base_Type
(Ent
))
526 or else Ekind
(Ent
) = E_Package
527 or else Is_Generic_Unit
(Ent
)
530 New_Occurrence_Of
(RTE
(RE_Null_Address
), Sloc
(N
)));
532 -- Anything else is illegal
535 Error_Attr
("invalid prefix for % attribute", P
);
541 elsif Is_Object_Reference
(P
) then
544 -- Subprogram called using dot notation
546 elsif Nkind
(P
) = N_Selected_Component
547 and then Is_Subprogram
(Entity
(Selector_Name
(P
)))
551 -- What exactly are we allowing here ??? and is this properly
552 -- documented in the sinfo documentation for this node ???
554 elsif Relaxed_RM_Semantics
555 and then Nkind
(P
) = N_Attribute_Reference
559 -- All other non-entity name cases are illegal
562 Error_Attr
("invalid prefix for % attribute", P
);
566 ------------------------------
567 -- Analyze_Access_Attribute --
568 ------------------------------
570 procedure Analyze_Access_Attribute
is
571 Acc_Type
: Entity_Id
;
576 function Build_Access_Object_Type
(DT
: Entity_Id
) return Entity_Id
;
577 -- Build an access-to-object type whose designated type is DT,
578 -- and whose Ekind is appropriate to the attribute type. The
579 -- type that is constructed is returned as the result.
581 procedure Build_Access_Subprogram_Type
(P
: Node_Id
);
582 -- Build an access to subprogram whose designated type is the type of
583 -- the prefix. If prefix is overloaded, so is the node itself. The
584 -- result is stored in Acc_Type.
586 function OK_Self_Reference
return Boolean;
587 -- An access reference whose prefix is a type can legally appear
588 -- within an aggregate, where it is obtained by expansion of
589 -- a defaulted aggregate. The enclosing aggregate that contains
590 -- the self-referenced is flagged so that the self-reference can
591 -- be expanded into a reference to the target object (see exp_aggr).
593 ------------------------------
594 -- Build_Access_Object_Type --
595 ------------------------------
597 function Build_Access_Object_Type
(DT
: Entity_Id
) return Entity_Id
is
598 Typ
: constant Entity_Id
:=
600 (E_Access_Attribute_Type
, Current_Scope
, Loc
, 'A');
602 Set_Etype
(Typ
, Typ
);
604 Set_Associated_Node_For_Itype
(Typ
, N
);
605 Set_Directly_Designated_Type
(Typ
, DT
);
607 end Build_Access_Object_Type
;
609 ----------------------------------
610 -- Build_Access_Subprogram_Type --
611 ----------------------------------
613 procedure Build_Access_Subprogram_Type
(P
: Node_Id
) is
614 Index
: Interp_Index
;
617 procedure Check_Local_Access
(E
: Entity_Id
);
618 -- Deal with possible access to local subprogram. If we have such
619 -- an access, we set a flag to kill all tracked values on any call
620 -- because this access value may be passed around, and any called
621 -- code might use it to access a local procedure which clobbers a
622 -- tracked value. If the scope is a loop or block, indicate that
623 -- value tracking is disabled for the enclosing subprogram.
625 function Get_Kind
(E
: Entity_Id
) return Entity_Kind
;
626 -- Distinguish between access to regular/protected subprograms
628 ------------------------
629 -- Check_Local_Access --
630 ------------------------
632 procedure Check_Local_Access
(E
: Entity_Id
) is
634 if not Is_Library_Level_Entity
(E
) then
635 Set_Suppress_Value_Tracking_On_Call
(Current_Scope
);
636 Set_Suppress_Value_Tracking_On_Call
637 (Nearest_Dynamic_Scope
(Current_Scope
));
639 end Check_Local_Access
;
645 function Get_Kind
(E
: Entity_Id
) return Entity_Kind
is
647 if Convention
(E
) = Convention_Protected
then
648 return E_Access_Protected_Subprogram_Type
;
650 return E_Access_Subprogram_Type
;
654 -- Start of processing for Build_Access_Subprogram_Type
657 -- In the case of an access to subprogram, use the name of the
658 -- subprogram itself as the designated type. Type-checking in
659 -- this case compares the signatures of the designated types.
661 -- Note: This fragment of the tree is temporarily malformed
662 -- because the correct tree requires an E_Subprogram_Type entity
663 -- as the designated type. In most cases this designated type is
664 -- later overridden by the semantics with the type imposed by the
665 -- context during the resolution phase. In the specific case of
666 -- the expression Address!(Prim'Unrestricted_Access), used to
667 -- initialize slots of dispatch tables, this work will be done by
668 -- the expander (see Exp_Aggr).
670 -- The reason to temporarily add this kind of node to the tree
671 -- instead of a proper E_Subprogram_Type itype, is the following:
672 -- in case of errors found in the source file we report better
673 -- error messages. For example, instead of generating the
676 -- "expected access to subprogram with profile
677 -- defined at line X"
679 -- we currently generate:
681 -- "expected access to function Z defined at line X"
683 Set_Etype
(N
, Any_Type
);
685 if not Is_Overloaded
(P
) then
686 Check_Local_Access
(Entity
(P
));
688 if not Is_Intrinsic_Subprogram
(Entity
(P
)) then
689 Acc_Type
:= Create_Itype
(Get_Kind
(Entity
(P
)), N
);
690 Set_Is_Public
(Acc_Type
, False);
691 Set_Etype
(Acc_Type
, Acc_Type
);
692 Set_Convention
(Acc_Type
, Convention
(Entity
(P
)));
693 Set_Directly_Designated_Type
(Acc_Type
, Entity
(P
));
694 Set_Etype
(N
, Acc_Type
);
695 Freeze_Before
(N
, Acc_Type
);
699 Get_First_Interp
(P
, Index
, It
);
700 while Present
(It
.Nam
) loop
701 Check_Local_Access
(It
.Nam
);
703 if not Is_Intrinsic_Subprogram
(It
.Nam
) then
704 Acc_Type
:= Create_Itype
(Get_Kind
(It
.Nam
), N
);
705 Set_Is_Public
(Acc_Type
, False);
706 Set_Etype
(Acc_Type
, Acc_Type
);
707 Set_Convention
(Acc_Type
, Convention
(It
.Nam
));
708 Set_Directly_Designated_Type
(Acc_Type
, It
.Nam
);
709 Add_One_Interp
(N
, Acc_Type
, Acc_Type
);
710 Freeze_Before
(N
, Acc_Type
);
713 Get_Next_Interp
(Index
, It
);
717 -- Cannot be applied to intrinsic. Looking at the tests above,
718 -- the only way Etype (N) can still be set to Any_Type is if
719 -- Is_Intrinsic_Subprogram was True for some referenced entity.
721 if Etype
(N
) = Any_Type
then
722 Error_Attr_P
("prefix of % attribute cannot be intrinsic");
724 end Build_Access_Subprogram_Type
;
726 ----------------------
727 -- OK_Self_Reference --
728 ----------------------
730 function OK_Self_Reference
return Boolean is
737 (Nkind
(Par
) = N_Component_Association
738 or else Nkind
(Par
) in N_Subexpr
)
740 if Nkind_In
(Par
, N_Aggregate
, N_Extension_Aggregate
) then
741 if Etype
(Par
) = Typ
then
742 Set_Has_Self_Reference
(Par
);
750 -- No enclosing aggregate, or not a self-reference
753 end OK_Self_Reference
;
755 -- Start of processing for Analyze_Access_Attribute
758 Check_SPARK_Restriction_On_Attribute
;
761 if Nkind
(P
) = N_Character_Literal
then
763 ("prefix of % attribute cannot be enumeration literal");
766 -- Case of access to subprogram
768 if Is_Entity_Name
(P
) and then Is_Overloadable
(Entity
(P
)) then
769 if Has_Pragma_Inline_Always
(Entity
(P
)) then
771 ("prefix of % attribute cannot be Inline_Always subprogram");
773 elsif Aname
= Name_Unchecked_Access
then
774 Error_Attr
("attribute% cannot be applied to a subprogram", P
);
776 elsif Is_Ghost_Subprogram
(Entity
(P
)) then
778 ("prefix of % attribute cannot be a ghost subprogram");
781 -- Issue an error if the prefix denotes an eliminated subprogram
783 Check_For_Eliminated_Subprogram
(P
, Entity
(P
));
785 -- Check for obsolescent subprogram reference
787 Check_Obsolescent_2005_Entity
(Entity
(P
), P
);
789 -- Build the appropriate subprogram type
791 Build_Access_Subprogram_Type
(P
);
793 -- For P'Access or P'Unrestricted_Access, where P is a nested
794 -- subprogram, we might be passing P to another subprogram (but we
795 -- don't check that here), which might call P. P could modify
796 -- local variables, so we need to kill current values. It is
797 -- important not to do this for library-level subprograms, because
798 -- Kill_Current_Values is very inefficient in the case of library
799 -- level packages with lots of tagged types.
801 if Is_Library_Level_Entity
(Entity
(Prefix
(N
))) then
804 -- Do not kill values on nodes initializing dispatch tables
805 -- slots. The construct Prim_Ptr!(Prim'Unrestricted_Access)
806 -- is currently generated by the expander only for this
807 -- purpose. Done to keep the quality of warnings currently
808 -- generated by the compiler (otherwise any declaration of
809 -- a tagged type cleans constant indications from its scope).
811 elsif Nkind
(Parent
(N
)) = N_Unchecked_Type_Conversion
812 and then (Etype
(Parent
(N
)) = RTE
(RE_Prim_Ptr
)
814 Etype
(Parent
(N
)) = RTE
(RE_Size_Ptr
))
815 and then Is_Dispatching_Operation
816 (Directly_Designated_Type
(Etype
(N
)))
824 -- In the static elaboration model, treat the attribute reference
825 -- as a call for elaboration purposes. Suppress this treatment
826 -- under debug flag. In any case, we are all done.
828 if not Dynamic_Elaboration_Checks
and not Debug_Flag_Dot_UU
then
834 -- Component is an operation of a protected type
836 elsif Nkind
(P
) = N_Selected_Component
837 and then Is_Overloadable
(Entity
(Selector_Name
(P
)))
839 if Ekind
(Entity
(Selector_Name
(P
))) = E_Entry
then
840 Error_Attr_P
("prefix of % attribute must be subprogram");
843 Build_Access_Subprogram_Type
(Selector_Name
(P
));
847 -- Deal with incorrect reference to a type, but note that some
848 -- accesses are allowed: references to the current type instance,
849 -- or in Ada 2005 self-referential pointer in a default-initialized
852 if Is_Entity_Name
(P
) then
855 -- The reference may appear in an aggregate that has been expanded
856 -- into a loop. Locate scope of type definition, if any.
858 Scop
:= Current_Scope
;
859 while Ekind
(Scop
) = E_Loop
loop
860 Scop
:= Scope
(Scop
);
863 if Is_Type
(Typ
) then
865 -- OK if we are within the scope of a limited type
866 -- let's mark the component as having per object constraint
868 if Is_Anonymous_Tagged_Base
(Scop
, Typ
) then
876 Q
: Node_Id
:= Parent
(N
);
880 and then Nkind
(Q
) /= N_Component_Declaration
886 Set_Has_Per_Object_Constraint
887 (Defining_Identifier
(Q
), True);
891 if Nkind
(P
) = N_Expanded_Name
then
893 ("current instance prefix must be a direct name", P
);
896 -- If a current instance attribute appears in a component
897 -- constraint it must appear alone; other contexts (spec-
898 -- expressions, within a task body) are not subject to this
901 if not In_Spec_Expression
902 and then not Has_Completion
(Scop
)
904 Nkind_In
(Parent
(N
), N_Discriminant_Association
,
905 N_Index_Or_Discriminant_Constraint
)
908 ("current instance attribute must appear alone", N
);
911 if Is_CPP_Class
(Root_Type
(Typ
)) then
913 ("??current instance unsupported for derivations of "
914 & "'C'P'P types", N
);
917 -- OK if we are in initialization procedure for the type
918 -- in question, in which case the reference to the type
919 -- is rewritten as a reference to the current object.
921 elsif Ekind
(Scop
) = E_Procedure
922 and then Is_Init_Proc
(Scop
)
923 and then Etype
(First_Formal
(Scop
)) = Typ
926 Make_Attribute_Reference
(Loc
,
927 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
928 Attribute_Name
=> Name_Unrestricted_Access
));
932 -- OK if a task type, this test needs sharpening up ???
934 elsif Is_Task_Type
(Typ
) then
937 -- OK if self-reference in an aggregate in Ada 2005, and
938 -- the reference comes from a copied default expression.
940 -- Note that we check legality of self-reference even if the
941 -- expression comes from source, e.g. when a single component
942 -- association in an aggregate has a box association.
944 elsif Ada_Version
>= Ada_2005
945 and then OK_Self_Reference
949 -- OK if reference to current instance of a protected object
951 elsif Is_Protected_Self_Reference
(P
) then
954 -- Otherwise we have an error case
957 Error_Attr
("% attribute cannot be applied to type", P
);
963 -- If we fall through, we have a normal access to object case
965 -- Unrestricted_Access is (for now) legal wherever an allocator would
966 -- be legal, so its Etype is set to E_Allocator. The expected type
967 -- of the other attributes is a general access type, and therefore
968 -- we label them with E_Access_Attribute_Type.
970 if not Is_Overloaded
(P
) then
971 Acc_Type
:= Build_Access_Object_Type
(P_Type
);
972 Set_Etype
(N
, Acc_Type
);
976 Index
: Interp_Index
;
979 Set_Etype
(N
, Any_Type
);
980 Get_First_Interp
(P
, Index
, It
);
981 while Present
(It
.Typ
) loop
982 Acc_Type
:= Build_Access_Object_Type
(It
.Typ
);
983 Add_One_Interp
(N
, Acc_Type
, Acc_Type
);
984 Get_Next_Interp
(Index
, It
);
989 -- Special cases when we can find a prefix that is an entity name
998 if Is_Entity_Name
(PP
) then
1001 -- If we have an access to an object, and the attribute
1002 -- comes from source, then set the object as potentially
1003 -- source modified. We do this because the resulting access
1004 -- pointer can be used to modify the variable, and we might
1005 -- not detect this, leading to some junk warnings.
1007 Set_Never_Set_In_Source
(Ent
, False);
1009 -- Mark entity as address taken, and kill current values
1011 Set_Address_Taken
(Ent
);
1012 Kill_Current_Values
(Ent
);
1015 elsif Nkind_In
(PP
, N_Selected_Component
,
1016 N_Indexed_Component
)
1026 -- Check for aliased view.. We allow a nonaliased prefix when within
1027 -- an instance because the prefix may have been a tagged formal
1028 -- object, which is defined to be aliased even when the actual
1029 -- might not be (other instance cases will have been caught in the
1030 -- generic). Similarly, within an inlined body we know that the
1031 -- attribute is legal in the original subprogram, and therefore
1032 -- legal in the expansion.
1034 if not Is_Aliased_View
(P
)
1035 and then not In_Instance
1036 and then not In_Inlined_Body
1038 -- Here we have a non-aliased view. This is illegal unless we
1039 -- have the case of Unrestricted_Access, where for now we allow
1040 -- this (we will reject later if expected type is access to an
1041 -- unconstrained array with a thin pointer).
1043 if Aname
/= Name_Unrestricted_Access
then
1044 Error_Attr_P
("prefix of % attribute must be aliased");
1045 Check_No_Implicit_Aliasing
(P
);
1047 -- For Unrestricted_Access, record that prefix is not aliased
1048 -- to simplify legality check later on.
1051 Set_Non_Aliased_Prefix
(N
);
1054 -- If we have an aliased view, and we have Unrestricted_Access, then
1055 -- output a warning that Unchecked_Access would have been fine, and
1056 -- change the node to be Unchecked_Access.
1059 -- For now, hold off on this change ???
1063 end Analyze_Access_Attribute
;
1065 ---------------------------------
1066 -- Bad_Attribute_For_Predicate --
1067 ---------------------------------
1069 procedure Bad_Attribute_For_Predicate
is
1071 if Is_Scalar_Type
(P_Type
)
1072 and then Comes_From_Source
(N
)
1074 Error_Msg_Name_1
:= Aname
;
1075 Bad_Predicated_Subtype_Use
1076 ("type& has predicates, attribute % not allowed", N
, P_Type
);
1078 end Bad_Attribute_For_Predicate
;
1080 --------------------------------
1081 -- Check_Array_Or_Scalar_Type --
1082 --------------------------------
1084 procedure Check_Array_Or_Scalar_Type
is
1088 -- Dimension number for array attributes
1091 -- Case of string literal or string literal subtype. These cases
1092 -- cannot arise from legal Ada code, but the expander is allowed
1093 -- to generate them. They require special handling because string
1094 -- literal subtypes do not have standard bounds (the whole idea
1095 -- of these subtypes is to avoid having to generate the bounds)
1097 if Ekind
(P_Type
) = E_String_Literal_Subtype
then
1098 Set_Etype
(N
, Etype
(First_Index
(P_Base_Type
)));
1103 elsif Is_Scalar_Type
(P_Type
) then
1106 if Present
(E1
) then
1107 Error_Attr
("invalid argument in % attribute", E1
);
1109 Set_Etype
(N
, P_Base_Type
);
1113 -- The following is a special test to allow 'First to apply to
1114 -- private scalar types if the attribute comes from generated
1115 -- code. This occurs in the case of Normalize_Scalars code.
1117 elsif Is_Private_Type
(P_Type
)
1118 and then Present
(Full_View
(P_Type
))
1119 and then Is_Scalar_Type
(Full_View
(P_Type
))
1120 and then not Comes_From_Source
(N
)
1122 Set_Etype
(N
, Implementation_Base_Type
(P_Type
));
1124 -- Array types other than string literal subtypes handled above
1129 -- We know prefix is an array type, or the name of an array
1130 -- object, and that the expression, if present, is static
1131 -- and within the range of the dimensions of the type.
1133 pragma Assert
(Is_Array_Type
(P_Type
));
1134 Index
:= First_Index
(P_Base_Type
);
1138 -- First dimension assumed
1140 Set_Etype
(N
, Base_Type
(Etype
(Index
)));
1143 D
:= UI_To_Int
(Intval
(E1
));
1145 for J
in 1 .. D
- 1 loop
1149 Set_Etype
(N
, Base_Type
(Etype
(Index
)));
1150 Set_Etype
(E1
, Standard_Integer
);
1153 end Check_Array_Or_Scalar_Type
;
1155 ----------------------
1156 -- Check_Array_Type --
1157 ----------------------
1159 procedure Check_Array_Type
is
1161 -- Dimension number for array attributes
1164 -- If the type is a string literal type, then this must be generated
1165 -- internally, and no further check is required on its legality.
1167 if Ekind
(P_Type
) = E_String_Literal_Subtype
then
1170 -- If the type is a composite, it is an illegal aggregate, no point
1173 elsif P_Type
= Any_Composite
then
1174 raise Bad_Attribute
;
1177 -- Normal case of array type or subtype
1179 Check_Either_E0_Or_E1
;
1182 if Is_Array_Type
(P_Type
) then
1183 if not Is_Constrained
(P_Type
)
1184 and then Is_Entity_Name
(P
)
1185 and then Is_Type
(Entity
(P
))
1187 -- Note: we do not call Error_Attr here, since we prefer to
1188 -- continue, using the relevant index type of the array,
1189 -- even though it is unconstrained. This gives better error
1190 -- recovery behavior.
1192 Error_Msg_Name_1
:= Aname
;
1194 ("prefix for % attribute must be constrained array", P
);
1197 -- The attribute reference freezes the type, and thus the
1198 -- component type, even if the attribute may not depend on the
1199 -- component. Diagnose arrays with incomplete components now.
1200 -- If the prefix is an access to array, this does not freeze
1201 -- the designated type.
1203 if Nkind
(P
) /= N_Explicit_Dereference
then
1204 Check_Fully_Declared
(Component_Type
(P_Type
), P
);
1207 D
:= Number_Dimensions
(P_Type
);
1210 if Is_Private_Type
(P_Type
) then
1211 Error_Attr_P
("prefix for % attribute may not be private type");
1213 elsif Is_Access_Type
(P_Type
)
1214 and then Is_Array_Type
(Designated_Type
(P_Type
))
1215 and then Is_Entity_Name
(P
)
1216 and then Is_Type
(Entity
(P
))
1218 Error_Attr_P
("prefix of % attribute cannot be access type");
1220 elsif Attr_Id
= Attribute_First
1222 Attr_Id
= Attribute_Last
1224 Error_Attr
("invalid prefix for % attribute", P
);
1227 Error_Attr_P
("prefix for % attribute must be array");
1231 if Present
(E1
) then
1232 Resolve
(E1
, Any_Integer
);
1233 Set_Etype
(E1
, Standard_Integer
);
1235 if not Is_OK_Static_Expression
(E1
)
1236 or else Raises_Constraint_Error
(E1
)
1238 Flag_Non_Static_Expr
1239 ("expression for dimension must be static!", E1
);
1242 elsif UI_To_Int
(Expr_Value
(E1
)) > D
1243 or else UI_To_Int
(Expr_Value
(E1
)) < 1
1245 Error_Attr
("invalid dimension number for array type", E1
);
1249 if (Style_Check
and Style_Check_Array_Attribute_Index
)
1250 and then Comes_From_Source
(N
)
1252 Style
.Check_Array_Attribute_Index
(N
, E1
, D
);
1254 end Check_Array_Type
;
1256 -------------------------
1257 -- Check_Asm_Attribute --
1258 -------------------------
1260 procedure Check_Asm_Attribute
is
1265 -- Check first argument is static string expression
1267 Analyze_And_Resolve
(E1
, Standard_String
);
1269 if Etype
(E1
) = Any_Type
then
1272 elsif not Is_OK_Static_Expression
(E1
) then
1273 Flag_Non_Static_Expr
1274 ("constraint argument must be static string expression!", E1
);
1278 -- Check second argument is right type
1280 Analyze_And_Resolve
(E2
, Entity
(P
));
1282 -- Note: that is all we need to do, we don't need to check
1283 -- that it appears in a correct context. The Ada type system
1284 -- will do that for us.
1286 end Check_Asm_Attribute
;
1288 ---------------------
1289 -- Check_Component --
1290 ---------------------
1292 procedure Check_Component
is
1296 if Nkind
(P
) /= N_Selected_Component
1298 (Ekind
(Entity
(Selector_Name
(P
))) /= E_Component
1300 Ekind
(Entity
(Selector_Name
(P
))) /= E_Discriminant
)
1302 Error_Attr_P
("prefix for % attribute must be selected component");
1304 end Check_Component
;
1306 ------------------------------------
1307 -- Check_Decimal_Fixed_Point_Type --
1308 ------------------------------------
1310 procedure Check_Decimal_Fixed_Point_Type
is
1314 if not Is_Decimal_Fixed_Point_Type
(P_Type
) then
1315 Error_Attr_P
("prefix of % attribute must be decimal type");
1317 end Check_Decimal_Fixed_Point_Type
;
1319 -----------------------
1320 -- Check_Dereference --
1321 -----------------------
1323 procedure Check_Dereference
is
1326 -- Case of a subtype mark
1328 if Is_Entity_Name
(P
) and then Is_Type
(Entity
(P
)) then
1332 -- Case of an expression
1336 if Is_Access_Type
(P_Type
) then
1338 -- If there is an implicit dereference, then we must freeze the
1339 -- designated type of the access type, since the type of the
1340 -- referenced array is this type (see AI95-00106).
1342 -- As done elsewhere, freezing must not happen when pre-analyzing
1343 -- a pre- or postcondition or a default value for an object or for
1344 -- a formal parameter.
1346 if not In_Spec_Expression
then
1347 Freeze_Before
(N
, Designated_Type
(P_Type
));
1351 Make_Explicit_Dereference
(Sloc
(P
),
1352 Prefix
=> Relocate_Node
(P
)));
1354 Analyze_And_Resolve
(P
);
1355 P_Type
:= Etype
(P
);
1357 if P_Type
= Any_Type
then
1358 raise Bad_Attribute
;
1361 P_Base_Type
:= Base_Type
(P_Type
);
1363 end Check_Dereference
;
1365 -------------------------
1366 -- Check_Discrete_Type --
1367 -------------------------
1369 procedure Check_Discrete_Type
is
1373 if not Is_Discrete_Type
(P_Type
) then
1374 Error_Attr_P
("prefix of % attribute must be discrete type");
1376 end Check_Discrete_Type
;
1382 procedure Check_E0
is
1384 if Present
(E1
) then
1385 Unexpected_Argument
(E1
);
1393 procedure Check_E1
is
1395 Check_Either_E0_Or_E1
;
1399 -- Special-case attributes that are functions and that appear as
1400 -- the prefix of another attribute. Error is posted on parent.
1402 if Nkind
(Parent
(N
)) = N_Attribute_Reference
1403 and then Nam_In
(Attribute_Name
(Parent
(N
)), Name_Address
,
1407 Error_Msg_Name_1
:= Attribute_Name
(Parent
(N
));
1408 Error_Msg_N
("illegal prefix for % attribute", Parent
(N
));
1409 Set_Etype
(Parent
(N
), Any_Type
);
1410 Set_Entity
(Parent
(N
), Any_Type
);
1411 raise Bad_Attribute
;
1414 Error_Attr
("missing argument for % attribute", N
);
1423 procedure Check_E2
is
1426 Error_Attr
("missing arguments for % attribute (2 required)", N
);
1428 Error_Attr
("missing argument for % attribute (2 required)", N
);
1432 ---------------------------
1433 -- Check_Either_E0_Or_E1 --
1434 ---------------------------
1436 procedure Check_Either_E0_Or_E1
is
1438 if Present
(E2
) then
1439 Unexpected_Argument
(E2
);
1441 end Check_Either_E0_Or_E1
;
1443 ----------------------
1444 -- Check_Enum_Image --
1445 ----------------------
1447 procedure Check_Enum_Image
is
1451 -- When an enumeration type appears in an attribute reference, all
1452 -- literals of the type are marked as referenced. This must only be
1453 -- done if the attribute reference appears in the current source.
1454 -- Otherwise the information on references may differ between a
1455 -- normal compilation and one that performs inlining.
1457 if Is_Enumeration_Type
(P_Base_Type
)
1458 and then In_Extended_Main_Code_Unit
(N
)
1460 Lit
:= First_Literal
(P_Base_Type
);
1461 while Present
(Lit
) loop
1462 Set_Referenced
(Lit
);
1466 end Check_Enum_Image
;
1468 ----------------------------
1469 -- Check_First_Last_Valid --
1470 ----------------------------
1472 procedure Check_First_Last_Valid
is
1474 Check_Discrete_Type
;
1476 -- Freeze the subtype now, so that the following test for predicates
1477 -- works (we set the predicates stuff up at freeze time)
1479 Insert_Actions
(N
, Freeze_Entity
(P_Type
, P
));
1481 -- Now test for dynamic predicate
1483 if Has_Predicates
(P_Type
)
1484 and then not (Has_Static_Predicate
(P_Type
))
1487 ("prefix of % attribute may not have dynamic predicate");
1490 -- Check non-static subtype
1492 if not Is_OK_Static_Subtype
(P_Type
) then
1493 Error_Attr_P
("prefix of % attribute must be a static subtype");
1496 -- Test case for no values
1498 if Expr_Value
(Type_Low_Bound
(P_Type
)) >
1499 Expr_Value
(Type_High_Bound
(P_Type
))
1500 or else (Has_Predicates
(P_Type
)
1502 Is_Empty_List
(Static_Discrete_Predicate
(P_Type
)))
1505 ("prefix of % attribute must be subtype with "
1506 & "at least one value");
1508 end Check_First_Last_Valid
;
1510 ----------------------------
1511 -- Check_Fixed_Point_Type --
1512 ----------------------------
1514 procedure Check_Fixed_Point_Type
is
1518 if not Is_Fixed_Point_Type
(P_Type
) then
1519 Error_Attr_P
("prefix of % attribute must be fixed point type");
1521 end Check_Fixed_Point_Type
;
1523 ------------------------------
1524 -- Check_Fixed_Point_Type_0 --
1525 ------------------------------
1527 procedure Check_Fixed_Point_Type_0
is
1529 Check_Fixed_Point_Type
;
1531 end Check_Fixed_Point_Type_0
;
1533 -------------------------------
1534 -- Check_Floating_Point_Type --
1535 -------------------------------
1537 procedure Check_Floating_Point_Type
is
1541 if not Is_Floating_Point_Type
(P_Type
) then
1542 Error_Attr_P
("prefix of % attribute must be float type");
1544 end Check_Floating_Point_Type
;
1546 ---------------------------------
1547 -- Check_Floating_Point_Type_0 --
1548 ---------------------------------
1550 procedure Check_Floating_Point_Type_0
is
1552 Check_Floating_Point_Type
;
1554 end Check_Floating_Point_Type_0
;
1556 ---------------------------------
1557 -- Check_Floating_Point_Type_1 --
1558 ---------------------------------
1560 procedure Check_Floating_Point_Type_1
is
1562 Check_Floating_Point_Type
;
1564 end Check_Floating_Point_Type_1
;
1566 ---------------------------------
1567 -- Check_Floating_Point_Type_2 --
1568 ---------------------------------
1570 procedure Check_Floating_Point_Type_2
is
1572 Check_Floating_Point_Type
;
1574 end Check_Floating_Point_Type_2
;
1576 ------------------------
1577 -- Check_Integer_Type --
1578 ------------------------
1580 procedure Check_Integer_Type
is
1584 if not Is_Integer_Type
(P_Type
) then
1585 Error_Attr_P
("prefix of % attribute must be integer type");
1587 end Check_Integer_Type
;
1589 --------------------------------
1590 -- Check_Modular_Integer_Type --
1591 --------------------------------
1593 procedure Check_Modular_Integer_Type
is
1597 if not Is_Modular_Integer_Type
(P_Type
) then
1599 ("prefix of % attribute must be modular integer type");
1601 end Check_Modular_Integer_Type
;
1603 ------------------------
1604 -- Check_Not_CPP_Type --
1605 ------------------------
1607 procedure Check_Not_CPP_Type
is
1609 if Is_Tagged_Type
(Etype
(P
))
1610 and then Convention
(Etype
(P
)) = Convention_CPP
1611 and then Is_CPP_Class
(Root_Type
(Etype
(P
)))
1614 ("invalid use of % attribute with 'C'P'P tagged type");
1616 end Check_Not_CPP_Type
;
1618 -------------------------------
1619 -- Check_Not_Incomplete_Type --
1620 -------------------------------
1622 procedure Check_Not_Incomplete_Type
is
1627 -- Ada 2005 (AI-50217, AI-326): If the prefix is an explicit
1628 -- dereference we have to check wrong uses of incomplete types
1629 -- (other wrong uses are checked at their freezing point).
1631 -- Example 1: Limited-with
1633 -- limited with Pkg;
1635 -- type Acc is access Pkg.T;
1637 -- S : Integer := X.all'Size; -- ERROR
1640 -- Example 2: Tagged incomplete
1642 -- type T is tagged;
1643 -- type Acc is access all T;
1645 -- S : constant Integer := X.all'Size; -- ERROR
1646 -- procedure Q (Obj : Integer := X.all'Alignment); -- ERROR
1648 if Ada_Version
>= Ada_2005
1649 and then Nkind
(P
) = N_Explicit_Dereference
1652 while Nkind
(E
) = N_Explicit_Dereference
loop
1658 if From_Limited_With
(Typ
) then
1660 ("prefix of % attribute cannot be an incomplete type");
1663 if Is_Access_Type
(Typ
) then
1664 Typ
:= Directly_Designated_Type
(Typ
);
1667 if Is_Class_Wide_Type
(Typ
) then
1668 Typ
:= Root_Type
(Typ
);
1671 -- A legal use of a shadow entity occurs only when the unit
1672 -- where the non-limited view resides is imported via a regular
1673 -- with clause in the current body. Such references to shadow
1674 -- entities may occur in subprogram formals.
1676 if Is_Incomplete_Type
(Typ
)
1677 and then From_Limited_With
(Typ
)
1678 and then Present
(Non_Limited_View
(Typ
))
1679 and then Is_Legal_Shadow_Entity_In_Body
(Typ
)
1681 Typ
:= Non_Limited_View
(Typ
);
1684 if Ekind
(Typ
) = E_Incomplete_Type
1685 and then No
(Full_View
(Typ
))
1688 ("prefix of % attribute cannot be an incomplete type");
1693 if not Is_Entity_Name
(P
)
1694 or else not Is_Type
(Entity
(P
))
1695 or else In_Spec_Expression
1699 Check_Fully_Declared
(P_Type
, P
);
1701 end Check_Not_Incomplete_Type
;
1703 ----------------------------
1704 -- Check_Object_Reference --
1705 ----------------------------
1707 procedure Check_Object_Reference
(P
: Node_Id
) is
1711 -- If we need an object, and we have a prefix that is the name of
1712 -- a function entity, convert it into a function call.
1714 if Is_Entity_Name
(P
)
1715 and then Ekind
(Entity
(P
)) = E_Function
1717 Rtyp
:= Etype
(Entity
(P
));
1720 Make_Function_Call
(Sloc
(P
),
1721 Name
=> Relocate_Node
(P
)));
1723 Analyze_And_Resolve
(P
, Rtyp
);
1725 -- Otherwise we must have an object reference
1727 elsif not Is_Object_Reference
(P
) then
1728 Error_Attr_P
("prefix of % attribute must be object");
1730 end Check_Object_Reference
;
1732 ----------------------------
1733 -- Check_PolyORB_Attribute --
1734 ----------------------------
1736 procedure Check_PolyORB_Attribute
is
1738 Validate_Non_Static_Attribute_Function_Call
;
1743 if Get_PCS_Name
/= Name_PolyORB_DSA
then
1745 ("attribute% requires the 'Poly'O'R'B 'P'C'S", N
);
1747 end Check_PolyORB_Attribute
;
1749 ------------------------
1750 -- Check_Program_Unit --
1751 ------------------------
1753 procedure Check_Program_Unit
is
1755 if Is_Entity_Name
(P
) then
1757 K
: constant Entity_Kind
:= Ekind
(Entity
(P
));
1758 T
: constant Entity_Id
:= Etype
(Entity
(P
));
1761 if K
in Subprogram_Kind
1762 or else K
in Task_Kind
1763 or else K
in Protected_Kind
1764 or else K
= E_Package
1765 or else K
in Generic_Unit_Kind
1766 or else (K
= E_Variable
1770 Is_Protected_Type
(T
)))
1777 Error_Attr_P
("prefix of % attribute must be program unit");
1778 end Check_Program_Unit
;
1780 ---------------------
1781 -- Check_Real_Type --
1782 ---------------------
1784 procedure Check_Real_Type
is
1788 if not Is_Real_Type
(P_Type
) then
1789 Error_Attr_P
("prefix of % attribute must be real type");
1791 end Check_Real_Type
;
1793 -----------------------
1794 -- Check_Scalar_Type --
1795 -----------------------
1797 procedure Check_Scalar_Type
is
1801 if not Is_Scalar_Type
(P_Type
) then
1802 Error_Attr_P
("prefix of % attribute must be scalar type");
1804 end Check_Scalar_Type
;
1806 ------------------------------------------
1807 -- Check_SPARK_Restriction_On_Attribute --
1808 ------------------------------------------
1810 procedure Check_SPARK_Restriction_On_Attribute
is
1812 Error_Msg_Name_1
:= Aname
;
1813 Check_SPARK_Restriction
("attribute % is not allowed", P
);
1814 end Check_SPARK_Restriction_On_Attribute
;
1816 ---------------------------
1817 -- Check_Standard_Prefix --
1818 ---------------------------
1820 procedure Check_Standard_Prefix
is
1824 if Nkind
(P
) /= N_Identifier
or else Chars
(P
) /= Name_Standard
then
1825 Error_Attr
("only allowed prefix for % attribute is Standard", P
);
1827 end Check_Standard_Prefix
;
1829 ----------------------------
1830 -- Check_Stream_Attribute --
1831 ----------------------------
1833 procedure Check_Stream_Attribute
(Nam
: TSS_Name_Type
) is
1837 In_Shared_Var_Procs
: Boolean;
1838 -- True when compiling System.Shared_Storage.Shared_Var_Procs body.
1839 -- For this runtime package (always compiled in GNAT mode), we allow
1840 -- stream attributes references for limited types for the case where
1841 -- shared passive objects are implemented using stream attributes,
1842 -- which is the default in GNAT's persistent storage implementation.
1845 Validate_Non_Static_Attribute_Function_Call
;
1847 -- With the exception of 'Input, Stream attributes are procedures,
1848 -- and can only appear at the position of procedure calls. We check
1849 -- for this here, before they are rewritten, to give a more precise
1852 if Nam
= TSS_Stream_Input
then
1855 elsif Is_List_Member
(N
)
1856 and then not Nkind_In
(Parent
(N
), N_Procedure_Call_Statement
,
1863 ("invalid context for attribute%, which is a procedure", N
);
1867 Btyp
:= Implementation_Base_Type
(P_Type
);
1869 -- Stream attributes not allowed on limited types unless the
1870 -- attribute reference was generated by the expander (in which
1871 -- case the underlying type will be used, as described in Sinfo),
1872 -- or the attribute was specified explicitly for the type itself
1873 -- or one of its ancestors (taking visibility rules into account if
1874 -- in Ada 2005 mode), or a pragma Stream_Convert applies to Btyp
1875 -- (with no visibility restriction).
1878 Gen_Body
: constant Node_Id
:= Enclosing_Generic_Body
(N
);
1880 if Present
(Gen_Body
) then
1881 In_Shared_Var_Procs
:=
1882 Is_RTE
(Corresponding_Spec
(Gen_Body
), RE_Shared_Var_Procs
);
1884 In_Shared_Var_Procs
:= False;
1888 if (Comes_From_Source
(N
)
1889 and then not (In_Shared_Var_Procs
or In_Instance
))
1890 and then not Stream_Attribute_Available
(P_Type
, Nam
)
1891 and then not Has_Rep_Pragma
(Btyp
, Name_Stream_Convert
)
1893 Error_Msg_Name_1
:= Aname
;
1895 if Is_Limited_Type
(P_Type
) then
1897 ("limited type& has no% attribute", P
, P_Type
);
1898 Explain_Limited_Type
(P_Type
, P
);
1901 ("attribute% for type& is not available", P
, P_Type
);
1905 -- Check restriction violations
1907 -- First check the No_Streams restriction, which prohibits the use
1908 -- of explicit stream attributes in the source program. We do not
1909 -- prevent the occurrence of stream attributes in generated code,
1910 -- for instance those generated implicitly for dispatching purposes.
1912 if Comes_From_Source
(N
) then
1913 Check_Restriction
(No_Streams
, P
);
1916 -- AI05-0057: if restriction No_Default_Stream_Attributes is active,
1917 -- it is illegal to use a predefined elementary type stream attribute
1918 -- either by itself, or more importantly as part of the attribute
1919 -- subprogram for a composite type. However, if the broader
1920 -- restriction No_Streams is active, stream operations are not
1921 -- generated, and there is no error.
1923 if Restriction_Active
(No_Default_Stream_Attributes
)
1924 and then not Restriction_Active
(No_Streams
)
1930 if Nam
= TSS_Stream_Input
1932 Nam
= TSS_Stream_Read
1935 Type_Without_Stream_Operation
(P_Type
, TSS_Stream_Read
);
1938 Type_Without_Stream_Operation
(P_Type
, TSS_Stream_Write
);
1942 Check_Restriction
(No_Default_Stream_Attributes
, N
);
1945 ("missing user-defined Stream Read or Write for type&",
1947 if not Is_Elementary_Type
(P_Type
) then
1949 ("\which is a component of type&", N
, P_Type
);
1955 -- Check special case of Exception_Id and Exception_Occurrence which
1956 -- are not allowed for restriction No_Exception_Registration.
1958 if Restriction_Check_Required
(No_Exception_Registration
)
1959 and then (Is_RTE
(P_Type
, RE_Exception_Id
)
1961 Is_RTE
(P_Type
, RE_Exception_Occurrence
))
1963 Check_Restriction
(No_Exception_Registration
, P
);
1966 -- Here we must check that the first argument is an access type
1967 -- that is compatible with Ada.Streams.Root_Stream_Type'Class.
1969 Analyze_And_Resolve
(E1
);
1972 -- Note: the double call to Root_Type here is needed because the
1973 -- root type of a class-wide type is the corresponding type (e.g.
1974 -- X for X'Class, and we really want to go to the root.)
1976 if not Is_Access_Type
(Etyp
)
1977 or else Root_Type
(Root_Type
(Designated_Type
(Etyp
))) /=
1978 RTE
(RE_Root_Stream_Type
)
1981 ("expected access to Ada.Streams.Root_Stream_Type''Class", E1
);
1984 -- Check that the second argument is of the right type if there is
1985 -- one (the Input attribute has only one argument so this is skipped)
1987 if Present
(E2
) then
1990 if Nam
= TSS_Stream_Read
1991 and then not Is_OK_Variable_For_Out_Formal
(E2
)
1994 ("second argument of % attribute must be a variable", E2
);
1997 Resolve
(E2
, P_Type
);
2001 end Check_Stream_Attribute
;
2003 -------------------------
2004 -- Check_System_Prefix --
2005 -------------------------
2007 procedure Check_System_Prefix
is
2009 if Nkind
(P
) /= N_Identifier
or else Chars
(P
) /= Name_System
then
2010 Error_Attr
("only allowed prefix for % attribute is System", P
);
2012 end Check_System_Prefix
;
2014 -----------------------
2015 -- Check_Task_Prefix --
2016 -----------------------
2018 procedure Check_Task_Prefix
is
2022 -- Ada 2005 (AI-345): Attribute 'Terminated can be applied to
2023 -- task interface class-wide types.
2025 if Is_Task_Type
(Etype
(P
))
2026 or else (Is_Access_Type
(Etype
(P
))
2027 and then Is_Task_Type
(Designated_Type
(Etype
(P
))))
2028 or else (Ada_Version
>= Ada_2005
2029 and then Ekind
(Etype
(P
)) = E_Class_Wide_Type
2030 and then Is_Interface
(Etype
(P
))
2031 and then Is_Task_Interface
(Etype
(P
)))
2036 if Ada_Version
>= Ada_2005
then
2038 ("prefix of % attribute must be a task or a task " &
2039 "interface class-wide object");
2042 Error_Attr_P
("prefix of % attribute must be a task");
2045 end Check_Task_Prefix
;
2051 -- The possibilities are an entity name denoting a type, or an
2052 -- attribute reference that denotes a type (Base or Class). If
2053 -- the type is incomplete, replace it with its full view.
2055 procedure Check_Type
is
2057 if not Is_Entity_Name
(P
)
2058 or else not Is_Type
(Entity
(P
))
2060 Error_Attr_P
("prefix of % attribute must be a type");
2062 elsif Is_Protected_Self_Reference
(P
) then
2064 ("prefix of % attribute denotes current instance "
2065 & "(RM 9.4(21/2))");
2067 elsif Ekind
(Entity
(P
)) = E_Incomplete_Type
2068 and then Present
(Full_View
(Entity
(P
)))
2070 P_Type
:= Full_View
(Entity
(P
));
2071 Set_Entity
(P
, P_Type
);
2075 ---------------------
2076 -- Check_Unit_Name --
2077 ---------------------
2079 procedure Check_Unit_Name
(Nod
: Node_Id
) is
2081 if Nkind
(Nod
) = N_Identifier
then
2084 elsif Nkind_In
(Nod
, N_Selected_Component
, N_Expanded_Name
) then
2085 Check_Unit_Name
(Prefix
(Nod
));
2087 if Nkind
(Selector_Name
(Nod
)) = N_Identifier
then
2092 Error_Attr
("argument for % attribute must be unit name", P
);
2093 end Check_Unit_Name
;
2099 procedure Error_Attr
is
2101 Set_Etype
(N
, Any_Type
);
2102 Set_Entity
(N
, Any_Type
);
2103 raise Bad_Attribute
;
2106 procedure Error_Attr
(Msg
: String; Error_Node
: Node_Id
) is
2108 Error_Msg_Name_1
:= Aname
;
2109 Error_Msg_N
(Msg
, Error_Node
);
2117 procedure Error_Attr_P
(Msg
: String) is
2119 Error_Msg_Name_1
:= Aname
;
2120 Error_Msg_F
(Msg
, P
);
2124 ---------------------
2125 -- In_Refined_Post --
2126 ---------------------
2128 function In_Refined_Post
return Boolean is
2129 function Is_Refined_Post
(Prag
: Node_Id
) return Boolean;
2130 -- Determine whether Prag denotes one of the incarnations of pragma
2131 -- Refined_Post (either as is or pragma Check (Refined_Post, ...).
2133 ---------------------
2134 -- Is_Refined_Post --
2135 ---------------------
2137 function Is_Refined_Post
(Prag
: Node_Id
) return Boolean is
2138 Args
: constant List_Id
:= Pragma_Argument_Associations
(Prag
);
2139 Nam
: constant Name_Id
:= Pragma_Name
(Prag
);
2142 if Nam
= Name_Refined_Post
then
2145 elsif Nam
= Name_Check
then
2146 pragma Assert
(Present
(Args
));
2148 return Chars
(Expression
(First
(Args
))) = Name_Refined_Post
;
2152 end Is_Refined_Post
;
2158 -- Start of processing for In_Refined_Post
2162 while Present
(Stmt
) loop
2163 if Nkind
(Stmt
) = N_Pragma
and then Is_Refined_Post
(Stmt
) then
2166 -- Prevent the search from going too far
2168 elsif Is_Body_Or_Package_Declaration
(Stmt
) then
2172 Stmt
:= Parent
(Stmt
);
2176 end In_Refined_Post
;
2178 ----------------------------
2179 -- Legal_Formal_Attribute --
2180 ----------------------------
2182 procedure Legal_Formal_Attribute
is
2186 if not Is_Entity_Name
(P
)
2187 or else not Is_Type
(Entity
(P
))
2189 Error_Attr_P
("prefix of % attribute must be generic type");
2191 elsif Is_Generic_Actual_Type
(Entity
(P
))
2193 or else In_Inlined_Body
2197 elsif Is_Generic_Type
(Entity
(P
)) then
2198 if not Is_Indefinite_Subtype
(Entity
(P
)) then
2200 ("prefix of % attribute must be indefinite generic type");
2205 ("prefix of % attribute must be indefinite generic type");
2208 Set_Etype
(N
, Standard_Boolean
);
2209 end Legal_Formal_Attribute
;
2211 ---------------------------------------------------------------
2212 -- Max_Alignment_For_Allocation_Max_Size_In_Storage_Elements --
2213 ---------------------------------------------------------------
2215 procedure Max_Alignment_For_Allocation_Max_Size_In_Storage_Elements
is
2219 Check_Not_Incomplete_Type
;
2220 Set_Etype
(N
, Universal_Integer
);
2221 end Max_Alignment_For_Allocation_Max_Size_In_Storage_Elements
;
2227 procedure Min_Max
is
2231 Resolve
(E1
, P_Base_Type
);
2232 Resolve
(E2
, P_Base_Type
);
2233 Set_Etype
(N
, P_Base_Type
);
2235 -- Check for comparison on unordered enumeration type
2237 if Bad_Unordered_Enumeration_Reference
(N
, P_Base_Type
) then
2238 Error_Msg_Sloc
:= Sloc
(P_Base_Type
);
2240 ("comparison on unordered enumeration type& declared#?U?",
2245 ------------------------
2246 -- Standard_Attribute --
2247 ------------------------
2249 procedure Standard_Attribute
(Val
: Int
) is
2251 Check_Standard_Prefix
;
2252 Rewrite
(N
, Make_Integer_Literal
(Loc
, Val
));
2254 Set_Is_Static_Expression
(N
, True);
2255 end Standard_Attribute
;
2257 --------------------
2258 -- Uneval_Old_Msg --
2259 --------------------
2261 procedure Uneval_Old_Msg
is
2262 Uneval_Old_Setting
: Character;
2266 -- If from aspect, then Uneval_Old_Setting comes from flags in the
2267 -- N_Aspect_Specification node that corresponds to the attribute.
2269 -- First find the pragma in which we appear (note that at this stage,
2270 -- even if we appeared originally within an aspect specification, we
2271 -- are now within the corresponding pragma).
2275 Prag
:= Parent
(Prag
);
2276 exit when No
(Prag
) or else Nkind
(Prag
) = N_Pragma
;
2279 if Present
(Prag
) then
2280 if Uneval_Old_Accept
(Prag
) then
2281 Uneval_Old_Setting
:= 'A';
2282 elsif Uneval_Old_Warn
(Prag
) then
2283 Uneval_Old_Setting
:= 'W';
2285 Uneval_Old_Setting
:= 'E';
2288 -- If we did not find the pragma, that's odd, just use the setting
2289 -- from Opt.Uneval_Old. Perhaps this is due to a previous error?
2292 Uneval_Old_Setting
:= Opt
.Uneval_Old
;
2295 -- Processing depends on the setting of Uneval_Old
2297 case Uneval_Old_Setting
is
2300 ("prefix of attribute % that is potentially "
2301 & "unevaluated must denote an entity");
2304 Error_Msg_Name_1
:= Aname
;
2306 ("??prefix of attribute % appears in potentially "
2307 & "unevaluated context, exception may be raised", P
);
2313 raise Program_Error
;
2317 -------------------------
2318 -- Unexpected Argument --
2319 -------------------------
2321 procedure Unexpected_Argument
(En
: Node_Id
) is
2323 Error_Attr
("unexpected argument for % attribute", En
);
2324 end Unexpected_Argument
;
2326 -------------------------------------------------
2327 -- Validate_Non_Static_Attribute_Function_Call --
2328 -------------------------------------------------
2330 -- This function should be moved to Sem_Dist ???
2332 procedure Validate_Non_Static_Attribute_Function_Call
is
2334 if In_Preelaborated_Unit
2335 and then not In_Subprogram_Or_Concurrent_Unit
2337 Flag_Non_Static_Expr
2338 ("non-static function call in preelaborated unit!", N
);
2340 end Validate_Non_Static_Attribute_Function_Call
;
2342 -- Start of processing for Analyze_Attribute
2345 -- Immediate return if unrecognized attribute (already diagnosed
2346 -- by parser, so there is nothing more that we need to do)
2348 if not Is_Attribute_Name
(Aname
) then
2349 raise Bad_Attribute
;
2352 -- Deal with Ada 83 issues
2354 if Comes_From_Source
(N
) then
2355 if not Attribute_83
(Attr_Id
) then
2356 if Ada_Version
= Ada_83
and then Comes_From_Source
(N
) then
2357 Error_Msg_Name_1
:= Aname
;
2358 Error_Msg_N
("(Ada 83) attribute% is not standard??", N
);
2361 if Attribute_Impl_Def
(Attr_Id
) then
2362 Check_Restriction
(No_Implementation_Attributes
, N
);
2367 -- Deal with Ada 2005 attributes that are implementation attributes
2368 -- because they appear in a version of Ada before Ada 2005, and
2369 -- similarly for Ada 2012 attributes appearing in an earlier version.
2371 if (Attribute_05
(Attr_Id
) and then Ada_Version
< Ada_2005
)
2373 (Attribute_12
(Attr_Id
) and then Ada_Version
< Ada_2012
)
2375 Check_Restriction
(No_Implementation_Attributes
, N
);
2378 -- Remote access to subprogram type access attribute reference needs
2379 -- unanalyzed copy for tree transformation. The analyzed copy is used
2380 -- for its semantic information (whether prefix is a remote subprogram
2381 -- name), the unanalyzed copy is used to construct new subtree rooted
2382 -- with N_Aggregate which represents a fat pointer aggregate.
2384 if Aname
= Name_Access
then
2385 Discard_Node
(Copy_Separate_Tree
(N
));
2388 -- Analyze prefix and exit if error in analysis. If the prefix is an
2389 -- incomplete type, use full view if available. Note that there are
2390 -- some attributes for which we do not analyze the prefix, since the
2391 -- prefix is not a normal name, or else needs special handling.
2393 if Aname
/= Name_Elab_Body
and then
2394 Aname
/= Name_Elab_Spec
and then
2395 Aname
/= Name_Elab_Subp_Body
and then
2396 Aname
/= Name_UET_Address
and then
2397 Aname
/= Name_Enabled
and then
2401 P_Type
:= Etype
(P
);
2403 if Is_Entity_Name
(P
)
2404 and then Present
(Entity
(P
))
2405 and then Is_Type
(Entity
(P
))
2407 if Ekind
(Entity
(P
)) = E_Incomplete_Type
then
2408 P_Type
:= Get_Full_View
(P_Type
);
2409 Set_Entity
(P
, P_Type
);
2410 Set_Etype
(P
, P_Type
);
2412 elsif Entity
(P
) = Current_Scope
2413 and then Is_Record_Type
(Entity
(P
))
2415 -- Use of current instance within the type. Verify that if the
2416 -- attribute appears within a constraint, it yields an access
2417 -- type, other uses are illegal.
2425 and then Nkind
(Parent
(Par
)) /= N_Component_Definition
2427 Par
:= Parent
(Par
);
2431 and then Nkind
(Par
) = N_Subtype_Indication
2433 if Attr_Id
/= Attribute_Access
2434 and then Attr_Id
/= Attribute_Unchecked_Access
2435 and then Attr_Id
/= Attribute_Unrestricted_Access
2438 ("in a constraint the current instance can only"
2439 & " be used with an access attribute", N
);
2446 if P_Type
= Any_Type
then
2447 raise Bad_Attribute
;
2450 P_Base_Type
:= Base_Type
(P_Type
);
2453 -- Analyze expressions that may be present, exiting if an error occurs
2460 E1
:= First
(Exprs
);
2462 -- Skip analysis for case of Restriction_Set, we do not expect
2463 -- the argument to be analyzed in this case.
2465 if Aname
/= Name_Restriction_Set
then
2468 -- Check for missing/bad expression (result of previous error)
2470 if No
(E1
) or else Etype
(E1
) = Any_Type
then
2471 raise Bad_Attribute
;
2477 if Present
(E2
) then
2480 if Etype
(E2
) = Any_Type
then
2481 raise Bad_Attribute
;
2484 if Present
(Next
(E2
)) then
2485 Unexpected_Argument
(Next
(E2
));
2490 -- Cases where prefix must be resolvable by itself
2492 if Is_Overloaded
(P
)
2493 and then Aname
/= Name_Access
2494 and then Aname
/= Name_Address
2495 and then Aname
/= Name_Code_Address
2496 and then Aname
/= Name_Result
2497 and then Aname
/= Name_Unchecked_Access
2499 -- The prefix must be resolvable by itself, without reference to the
2500 -- attribute. One case that requires special handling is a prefix
2501 -- that is a function name, where one interpretation may be a
2502 -- parameterless call. Entry attributes are handled specially below.
2504 if Is_Entity_Name
(P
)
2505 and then not Nam_In
(Aname
, Name_Count
, Name_Caller
)
2507 Check_Parameterless_Call
(P
);
2510 if Is_Overloaded
(P
) then
2512 -- Ada 2005 (AI-345): Since protected and task types have
2513 -- primitive entry wrappers, the attributes Count, and Caller
2514 -- require a context check
2516 if Nam_In
(Aname
, Name_Count
, Name_Caller
) then
2518 Count
: Natural := 0;
2523 Get_First_Interp
(P
, I
, It
);
2524 while Present
(It
.Nam
) loop
2525 if Comes_From_Source
(It
.Nam
) then
2531 Get_Next_Interp
(I
, It
);
2535 Error_Attr
("ambiguous prefix for % attribute", P
);
2537 Set_Is_Overloaded
(P
, False);
2542 Error_Attr
("ambiguous prefix for % attribute", P
);
2547 -- In SPARK, attributes of private types are only allowed if the full
2548 -- type declaration is visible.
2550 -- Note: the check for Present (Entity (P)) defends against some error
2551 -- conditions where the Entity field is not set.
2553 if Is_Entity_Name
(P
) and then Present
(Entity
(P
))
2554 and then Is_Type
(Entity
(P
))
2555 and then Is_Private_Type
(P_Type
)
2556 and then not In_Open_Scopes
(Scope
(P_Type
))
2557 and then not In_Spec_Expression
2559 Check_SPARK_Restriction
("invisible attribute of type", N
);
2562 -- Remaining processing depends on attribute
2566 -- Attributes related to Ada 2012 iterators. Attribute specifications
2567 -- exist for these, but they cannot be queried.
2569 when Attribute_Constant_Indexing |
2570 Attribute_Default_Iterator |
2571 Attribute_Implicit_Dereference |
2572 Attribute_Iterator_Element |
2573 Attribute_Iterable |
2574 Attribute_Variable_Indexing
=>
2575 Error_Msg_N
("illegal attribute", N
);
2577 -- Internal attributes used to deal with Ada 2012 delayed aspects. These
2578 -- were already rejected by the parser. Thus they shouldn't appear here.
2580 when Internal_Attribute_Id
=>
2581 raise Program_Error
;
2587 when Attribute_Abort_Signal
=>
2588 Check_Standard_Prefix
;
2589 Rewrite
(N
, New_Occurrence_Of
(Stand
.Abort_Signal
, Loc
));
2596 when Attribute_Access
=>
2597 Analyze_Access_Attribute
;
2603 when Attribute_Address
=>
2606 Set_Etype
(N
, RTE
(RE_Address
));
2612 when Attribute_Address_Size
=>
2613 Standard_Attribute
(System_Address_Size
);
2619 when Attribute_Adjacent
=>
2620 Check_Floating_Point_Type_2
;
2621 Set_Etype
(N
, P_Base_Type
);
2622 Resolve
(E1
, P_Base_Type
);
2623 Resolve
(E2
, P_Base_Type
);
2629 when Attribute_Aft
=>
2630 Check_Fixed_Point_Type_0
;
2631 Set_Etype
(N
, Universal_Integer
);
2637 when Attribute_Alignment
=>
2639 -- Don't we need more checking here, cf Size ???
2642 Check_Not_Incomplete_Type
;
2644 Set_Etype
(N
, Universal_Integer
);
2650 when Attribute_Asm_Input
=>
2651 Check_Asm_Attribute
;
2653 -- The back-end may need to take the address of E2
2655 if Is_Entity_Name
(E2
) then
2656 Set_Address_Taken
(Entity
(E2
));
2659 Set_Etype
(N
, RTE
(RE_Asm_Input_Operand
));
2665 when Attribute_Asm_Output
=>
2666 Check_Asm_Attribute
;
2668 if Etype
(E2
) = Any_Type
then
2671 elsif Aname
= Name_Asm_Output
then
2672 if not Is_Variable
(E2
) then
2674 ("second argument for Asm_Output is not variable", E2
);
2678 Note_Possible_Modification
(E2
, Sure
=> True);
2680 -- The back-end may need to take the address of E2
2682 if Is_Entity_Name
(E2
) then
2683 Set_Address_Taken
(Entity
(E2
));
2686 Set_Etype
(N
, RTE
(RE_Asm_Output_Operand
));
2688 -----------------------------
2689 -- Atomic_Always_Lock_Free --
2690 -----------------------------
2692 when Attribute_Atomic_Always_Lock_Free
=>
2695 Set_Etype
(N
, Standard_Boolean
);
2701 -- Note: when the base attribute appears in the context of a subtype
2702 -- mark, the analysis is done by Sem_Ch8.Find_Type, rather than by
2703 -- the following circuit.
2705 when Attribute_Base
=> Base
: declare
2713 if Ada_Version
>= Ada_95
2714 and then not Is_Scalar_Type
(Typ
)
2715 and then not Is_Generic_Type
(Typ
)
2717 Error_Attr_P
("prefix of Base attribute must be scalar type");
2719 elsif Sloc
(Typ
) = Standard_Location
2720 and then Base_Type
(Typ
) = Typ
2721 and then Warn_On_Redundant_Constructs
2723 Error_Msg_NE
-- CODEFIX
2724 ("?r?redundant attribute, & is its own base type", N
, Typ
);
2727 if Nkind
(Parent
(N
)) /= N_Attribute_Reference
then
2728 Error_Msg_Name_1
:= Aname
;
2729 Check_SPARK_Restriction
2730 ("attribute% is only allowed as prefix of another attribute", P
);
2733 Set_Etype
(N
, Base_Type
(Entity
(P
)));
2734 Set_Entity
(N
, Base_Type
(Entity
(P
)));
2735 Rewrite
(N
, New_Occurrence_Of
(Entity
(N
), Loc
));
2743 when Attribute_Bit
=> Bit
:
2747 if not Is_Object_Reference
(P
) then
2748 Error_Attr_P
("prefix for % attribute must be object");
2750 -- What about the access object cases ???
2756 Set_Etype
(N
, Universal_Integer
);
2763 when Attribute_Bit_Order
=> Bit_Order
:
2768 if not Is_Record_Type
(P_Type
) then
2769 Error_Attr_P
("prefix of % attribute must be record type");
2772 if Bytes_Big_Endian
xor Reverse_Bit_Order
(P_Type
) then
2774 New_Occurrence_Of
(RTE
(RE_High_Order_First
), Loc
));
2777 New_Occurrence_Of
(RTE
(RE_Low_Order_First
), Loc
));
2780 Set_Etype
(N
, RTE
(RE_Bit_Order
));
2783 -- Reset incorrect indication of staticness
2785 Set_Is_Static_Expression
(N
, False);
2792 -- Note: in generated code, we can have a Bit_Position attribute
2793 -- applied to a (naked) record component (i.e. the prefix is an
2794 -- identifier that references an E_Component or E_Discriminant
2795 -- entity directly, and this is interpreted as expected by Gigi.
2796 -- The following code will not tolerate such usage, but when the
2797 -- expander creates this special case, it marks it as analyzed
2798 -- immediately and sets an appropriate type.
2800 when Attribute_Bit_Position
=>
2801 if Comes_From_Source
(N
) then
2805 Set_Etype
(N
, Universal_Integer
);
2811 when Attribute_Body_Version
=>
2814 Set_Etype
(N
, RTE
(RE_Version_String
));
2820 when Attribute_Callable
=>
2822 Set_Etype
(N
, Standard_Boolean
);
2829 when Attribute_Caller
=> Caller
: declare
2836 if Nkind_In
(P
, N_Identifier
, N_Expanded_Name
) then
2839 if not Is_Entry
(Ent
) then
2840 Error_Attr
("invalid entry name", N
);
2844 Error_Attr
("invalid entry name", N
);
2848 for J
in reverse 0 .. Scope_Stack
.Last
loop
2849 S
:= Scope_Stack
.Table
(J
).Entity
;
2851 if S
= Scope
(Ent
) then
2852 Error_Attr
("Caller must appear in matching accept or body", N
);
2858 Set_Etype
(N
, RTE
(RO_AT_Task_Id
));
2865 when Attribute_Ceiling
=>
2866 Check_Floating_Point_Type_1
;
2867 Set_Etype
(N
, P_Base_Type
);
2868 Resolve
(E1
, P_Base_Type
);
2874 when Attribute_Class
=>
2875 Check_Restriction
(No_Dispatch
, N
);
2879 -- Applying Class to untagged incomplete type is obsolescent in Ada
2880 -- 2005. Note that we can't test Is_Tagged_Type here on P_Type, since
2881 -- this flag gets set by Find_Type in this situation.
2883 if Restriction_Check_Required
(No_Obsolescent_Features
)
2884 and then Ada_Version
>= Ada_2005
2885 and then Ekind
(P_Type
) = E_Incomplete_Type
2888 DN
: constant Node_Id
:= Declaration_Node
(P_Type
);
2890 if Nkind
(DN
) = N_Incomplete_Type_Declaration
2891 and then not Tagged_Present
(DN
)
2893 Check_Restriction
(No_Obsolescent_Features
, P
);
2902 when Attribute_Code_Address
=>
2905 if Nkind
(P
) = N_Attribute_Reference
2906 and then Nam_In
(Attribute_Name
(P
), Name_Elab_Body
, Name_Elab_Spec
)
2910 elsif not Is_Entity_Name
(P
)
2911 or else (Ekind
(Entity
(P
)) /= E_Function
2913 Ekind
(Entity
(P
)) /= E_Procedure
)
2915 Error_Attr
("invalid prefix for % attribute", P
);
2916 Set_Address_Taken
(Entity
(P
));
2918 -- Issue an error if the prefix denotes an eliminated subprogram
2921 Check_For_Eliminated_Subprogram
(P
, Entity
(P
));
2924 Set_Etype
(N
, RTE
(RE_Address
));
2926 ----------------------
2927 -- Compiler_Version --
2928 ----------------------
2930 when Attribute_Compiler_Version
=>
2932 Check_Standard_Prefix
;
2933 Rewrite
(N
, Make_String_Literal
(Loc
, "GNAT " & Gnat_Version_String
));
2934 Analyze_And_Resolve
(N
, Standard_String
);
2935 Set_Is_Static_Expression
(N
, True);
2937 --------------------
2938 -- Component_Size --
2939 --------------------
2941 when Attribute_Component_Size
=>
2943 Set_Etype
(N
, Universal_Integer
);
2945 -- Note: unlike other array attributes, unconstrained arrays are OK
2947 if Is_Array_Type
(P_Type
) and then not Is_Constrained
(P_Type
) then
2957 when Attribute_Compose
=>
2958 Check_Floating_Point_Type_2
;
2959 Set_Etype
(N
, P_Base_Type
);
2960 Resolve
(E1
, P_Base_Type
);
2961 Resolve
(E2
, Any_Integer
);
2967 when Attribute_Constrained
=>
2969 Set_Etype
(N
, Standard_Boolean
);
2971 -- Case from RM J.4(2) of constrained applied to private type
2973 if Is_Entity_Name
(P
) and then Is_Type
(Entity
(P
)) then
2974 Check_Restriction
(No_Obsolescent_Features
, P
);
2976 if Warn_On_Obsolescent_Feature
then
2978 ("constrained for private type is an " &
2979 "obsolescent feature (RM J.4)?j?", N
);
2982 -- If we are within an instance, the attribute must be legal
2983 -- because it was valid in the generic unit. Ditto if this is
2984 -- an inlining of a function declared in an instance.
2986 if In_Instance
or else In_Inlined_Body
then
2989 -- For sure OK if we have a real private type itself, but must
2990 -- be completed, cannot apply Constrained to incomplete type.
2992 elsif Is_Private_Type
(Entity
(P
)) then
2994 -- Note: this is one of the Annex J features that does not
2995 -- generate a warning from -gnatwj, since in fact it seems
2996 -- very useful, and is used in the GNAT runtime.
2998 Check_Not_Incomplete_Type
;
3002 -- Normal (non-obsolescent case) of application to object of
3003 -- a discriminated type.
3006 Check_Object_Reference
(P
);
3008 -- If N does not come from source, then we allow the
3009 -- the attribute prefix to be of a private type whose
3010 -- full type has discriminants. This occurs in cases
3011 -- involving expanded calls to stream attributes.
3013 if not Comes_From_Source
(N
) then
3014 P_Type
:= Underlying_Type
(P_Type
);
3017 -- Must have discriminants or be an access type designating
3018 -- a type with discriminants. If it is a classwide type it
3019 -- has unknown discriminants.
3021 if Has_Discriminants
(P_Type
)
3022 or else Has_Unknown_Discriminants
(P_Type
)
3024 (Is_Access_Type
(P_Type
)
3025 and then Has_Discriminants
(Designated_Type
(P_Type
)))
3029 -- The rule given in 3.7.2 is part of static semantics, but the
3030 -- intent is clearly that it be treated as a legality rule, and
3031 -- rechecked in the visible part of an instance. Nevertheless
3032 -- the intent also seems to be it should legally apply to the
3033 -- actual of a formal with unknown discriminants, regardless of
3034 -- whether the actual has discriminants, in which case the value
3035 -- of the attribute is determined using the J.4 rules. This choice
3036 -- seems the most useful, and is compatible with existing tests.
3038 elsif In_Instance
then
3041 -- Also allow an object of a generic type if extensions allowed
3042 -- and allow this for any type at all. (this may be obsolete ???)
3044 elsif (Is_Generic_Type
(P_Type
)
3045 or else Is_Generic_Actual_Type
(P_Type
))
3046 and then Extensions_Allowed
3052 -- Fall through if bad prefix
3055 ("prefix of % attribute must be object of discriminated type");
3061 when Attribute_Copy_Sign
=>
3062 Check_Floating_Point_Type_2
;
3063 Set_Etype
(N
, P_Base_Type
);
3064 Resolve
(E1
, P_Base_Type
);
3065 Resolve
(E2
, P_Base_Type
);
3071 when Attribute_Count
=> Count
:
3080 if Nkind_In
(P
, N_Identifier
, N_Expanded_Name
) then
3083 if Ekind
(Ent
) /= E_Entry
then
3084 Error_Attr
("invalid entry name", N
);
3087 elsif Nkind
(P
) = N_Indexed_Component
then
3088 if not Is_Entity_Name
(Prefix
(P
))
3089 or else No
(Entity
(Prefix
(P
)))
3090 or else Ekind
(Entity
(Prefix
(P
))) /= E_Entry_Family
3092 if Nkind
(Prefix
(P
)) = N_Selected_Component
3093 and then Present
(Entity
(Selector_Name
(Prefix
(P
))))
3094 and then Ekind
(Entity
(Selector_Name
(Prefix
(P
)))) =
3098 ("attribute % must apply to entry of current task", P
);
3101 Error_Attr
("invalid entry family name", P
);
3106 Ent
:= Entity
(Prefix
(P
));
3109 elsif Nkind
(P
) = N_Selected_Component
3110 and then Present
(Entity
(Selector_Name
(P
)))
3111 and then Ekind
(Entity
(Selector_Name
(P
))) = E_Entry
3114 ("attribute % must apply to entry of current task", P
);
3117 Error_Attr
("invalid entry name", N
);
3121 for J
in reverse 0 .. Scope_Stack
.Last
loop
3122 S
:= Scope_Stack
.Table
(J
).Entity
;
3124 if S
= Scope
(Ent
) then
3125 if Nkind
(P
) = N_Expanded_Name
then
3126 Tsk
:= Entity
(Prefix
(P
));
3128 -- The prefix denotes either the task type, or else a
3129 -- single task whose task type is being analyzed.
3131 if (Is_Type
(Tsk
) and then Tsk
= S
)
3132 or else (not Is_Type
(Tsk
)
3133 and then Etype
(Tsk
) = S
3134 and then not (Comes_From_Source
(S
)))
3139 ("Attribute % must apply to entry of current task", N
);
3145 elsif Ekind
(Scope
(Ent
)) in Task_Kind
3147 not Ekind_In
(S
, E_Loop
, E_Block
, E_Entry
, E_Entry_Family
)
3149 Error_Attr
("Attribute % cannot appear in inner unit", N
);
3151 elsif Ekind
(Scope
(Ent
)) = E_Protected_Type
3152 and then not Has_Completion
(Scope
(Ent
))
3154 Error_Attr
("attribute % can only be used inside body", N
);
3158 if Is_Overloaded
(P
) then
3160 Index
: Interp_Index
;
3164 Get_First_Interp
(P
, Index
, It
);
3165 while Present
(It
.Nam
) loop
3166 if It
.Nam
= Ent
then
3169 -- Ada 2005 (AI-345): Do not consider primitive entry
3170 -- wrappers generated for task or protected types.
3172 elsif Ada_Version
>= Ada_2005
3173 and then not Comes_From_Source
(It
.Nam
)
3178 Error_Attr
("ambiguous entry name", N
);
3181 Get_Next_Interp
(Index
, It
);
3186 Set_Etype
(N
, Universal_Integer
);
3189 -----------------------
3190 -- Default_Bit_Order --
3191 -----------------------
3193 when Attribute_Default_Bit_Order
=> Default_Bit_Order
:
3195 Check_Standard_Prefix
;
3197 if Bytes_Big_Endian
then
3199 Make_Integer_Literal
(Loc
, False_Value
));
3202 Make_Integer_Literal
(Loc
, True_Value
));
3205 Set_Etype
(N
, Universal_Integer
);
3206 Set_Is_Static_Expression
(N
);
3207 end Default_Bit_Order
;
3213 when Attribute_Definite
=>
3214 Legal_Formal_Attribute
;
3220 when Attribute_Delta
=>
3221 Check_Fixed_Point_Type_0
;
3222 Set_Etype
(N
, Universal_Real
);
3228 when Attribute_Denorm
=>
3229 Check_Floating_Point_Type_0
;
3230 Set_Etype
(N
, Standard_Boolean
);
3232 ---------------------
3233 -- Descriptor_Size --
3234 ---------------------
3236 when Attribute_Descriptor_Size
=>
3239 if not Is_Entity_Name
(P
) or else not Is_Type
(Entity
(P
)) then
3240 Error_Attr_P
("prefix of attribute % must denote a type");
3243 Set_Etype
(N
, Universal_Integer
);
3249 when Attribute_Digits
=>
3253 if not Is_Floating_Point_Type
(P_Type
)
3254 and then not Is_Decimal_Fixed_Point_Type
(P_Type
)
3257 ("prefix of % attribute must be float or decimal type");
3260 Set_Etype
(N
, Universal_Integer
);
3266 -- Also handles processing for Elab_Spec and Elab_Subp_Body
3268 when Attribute_Elab_Body |
3269 Attribute_Elab_Spec |
3270 Attribute_Elab_Subp_Body
=>
3273 Check_Unit_Name
(P
);
3274 Set_Etype
(N
, Standard_Void_Type
);
3276 -- We have to manually call the expander in this case to get
3277 -- the necessary expansion (normally attributes that return
3278 -- entities are not expanded).
3286 -- Shares processing with Elab_Body
3292 when Attribute_Elaborated
=>
3294 Check_Unit_Name
(P
);
3295 Set_Etype
(N
, Standard_Boolean
);
3301 when Attribute_Emax
=>
3302 Check_Floating_Point_Type_0
;
3303 Set_Etype
(N
, Universal_Integer
);
3309 when Attribute_Enabled
=>
3310 Check_Either_E0_Or_E1
;
3312 if Present
(E1
) then
3313 if not Is_Entity_Name
(E1
) or else No
(Entity
(E1
)) then
3314 Error_Msg_N
("entity name expected for Enabled attribute", E1
);
3319 if Nkind
(P
) /= N_Identifier
then
3320 Error_Msg_N
("identifier expected (check name)", P
);
3321 elsif Get_Check_Id
(Chars
(P
)) = No_Check_Id
then
3322 Error_Msg_N
("& is not a recognized check name", P
);
3325 Set_Etype
(N
, Standard_Boolean
);
3331 when Attribute_Enum_Rep
=> Enum_Rep
: declare
3333 if Present
(E1
) then
3335 Check_Discrete_Type
;
3336 Resolve
(E1
, P_Base_Type
);
3339 if not Is_Entity_Name
(P
)
3340 or else (not Is_Object
(Entity
(P
))
3341 and then Ekind
(Entity
(P
)) /= E_Enumeration_Literal
)
3344 ("prefix of % attribute must be " &
3345 "discrete type/object or enum literal");
3349 Set_Etype
(N
, Universal_Integer
);
3356 when Attribute_Enum_Val
=> Enum_Val
: begin
3360 if not Is_Enumeration_Type
(P_Type
) then
3361 Error_Attr_P
("prefix of % attribute must be enumeration type");
3364 -- If the enumeration type has a standard representation, the effect
3365 -- is the same as 'Val, so rewrite the attribute as a 'Val.
3367 if not Has_Non_Standard_Rep
(P_Base_Type
) then
3369 Make_Attribute_Reference
(Loc
,
3370 Prefix
=> Relocate_Node
(Prefix
(N
)),
3371 Attribute_Name
=> Name_Val
,
3372 Expressions
=> New_List
(Relocate_Node
(E1
))));
3373 Analyze_And_Resolve
(N
, P_Base_Type
);
3375 -- Non-standard representation case (enumeration with holes)
3379 Resolve
(E1
, Any_Integer
);
3380 Set_Etype
(N
, P_Base_Type
);
3388 when Attribute_Epsilon
=>
3389 Check_Floating_Point_Type_0
;
3390 Set_Etype
(N
, Universal_Real
);
3396 when Attribute_Exponent
=>
3397 Check_Floating_Point_Type_1
;
3398 Set_Etype
(N
, Universal_Integer
);
3399 Resolve
(E1
, P_Base_Type
);
3405 when Attribute_External_Tag
=>
3409 Set_Etype
(N
, Standard_String
);
3411 if not Is_Tagged_Type
(P_Type
) then
3412 Error_Attr_P
("prefix of % attribute must be tagged");
3419 when Attribute_Fast_Math
=>
3420 Check_Standard_Prefix
;
3421 Rewrite
(N
, New_Occurrence_Of
(Boolean_Literals
(Fast_Math
), Loc
));
3427 when Attribute_First
=>
3428 Check_Array_Or_Scalar_Type
;
3429 Bad_Attribute_For_Predicate
;
3435 when Attribute_First_Bit
=>
3437 Set_Etype
(N
, Universal_Integer
);
3443 when Attribute_First_Valid
=>
3444 Check_First_Last_Valid
;
3445 Set_Etype
(N
, P_Type
);
3451 when Attribute_Fixed_Value
=>
3453 Check_Fixed_Point_Type
;
3454 Resolve
(E1
, Any_Integer
);
3455 Set_Etype
(N
, P_Base_Type
);
3461 when Attribute_Floor
=>
3462 Check_Floating_Point_Type_1
;
3463 Set_Etype
(N
, P_Base_Type
);
3464 Resolve
(E1
, P_Base_Type
);
3470 when Attribute_Fore
=>
3471 Check_Fixed_Point_Type_0
;
3472 Set_Etype
(N
, Universal_Integer
);
3478 when Attribute_Fraction
=>
3479 Check_Floating_Point_Type_1
;
3480 Set_Etype
(N
, P_Base_Type
);
3481 Resolve
(E1
, P_Base_Type
);
3487 when Attribute_From_Any
=>
3489 Check_PolyORB_Attribute
;
3490 Set_Etype
(N
, P_Base_Type
);
3492 -----------------------
3493 -- Has_Access_Values --
3494 -----------------------
3496 when Attribute_Has_Access_Values
=>
3499 Set_Etype
(N
, Standard_Boolean
);
3501 ----------------------
3502 -- Has_Same_Storage --
3503 ----------------------
3505 when Attribute_Has_Same_Storage
=>
3508 -- The arguments must be objects of any type
3510 Analyze_And_Resolve
(P
);
3511 Analyze_And_Resolve
(E1
);
3512 Check_Object_Reference
(P
);
3513 Check_Object_Reference
(E1
);
3514 Set_Etype
(N
, Standard_Boolean
);
3516 -----------------------
3517 -- Has_Tagged_Values --
3518 -----------------------
3520 when Attribute_Has_Tagged_Values
=>
3523 Set_Etype
(N
, Standard_Boolean
);
3525 -----------------------
3526 -- Has_Discriminants --
3527 -----------------------
3529 when Attribute_Has_Discriminants
=>
3530 Legal_Formal_Attribute
;
3536 when Attribute_Identity
=>
3540 if Etype
(P
) = Standard_Exception_Type
then
3541 Set_Etype
(N
, RTE
(RE_Exception_Id
));
3543 -- Ada 2005 (AI-345): Attribute 'Identity may be applied to task
3544 -- interface class-wide types.
3546 elsif Is_Task_Type
(Etype
(P
))
3547 or else (Is_Access_Type
(Etype
(P
))
3548 and then Is_Task_Type
(Designated_Type
(Etype
(P
))))
3549 or else (Ada_Version
>= Ada_2005
3550 and then Ekind
(Etype
(P
)) = E_Class_Wide_Type
3551 and then Is_Interface
(Etype
(P
))
3552 and then Is_Task_Interface
(Etype
(P
)))
3555 Set_Etype
(N
, RTE
(RO_AT_Task_Id
));
3558 if Ada_Version
>= Ada_2005
then
3560 ("prefix of % attribute must be an exception, a " &
3561 "task or a task interface class-wide object");
3564 ("prefix of % attribute must be a task or an exception");
3572 when Attribute_Image
=> Image
:
3574 Check_SPARK_Restriction_On_Attribute
;
3576 Set_Etype
(N
, Standard_String
);
3578 if Is_Real_Type
(P_Type
) then
3579 if Ada_Version
= Ada_83
and then Comes_From_Source
(N
) then
3580 Error_Msg_Name_1
:= Aname
;
3582 ("(Ada 83) % attribute not allowed for real types", N
);
3586 if Is_Enumeration_Type
(P_Type
) then
3587 Check_Restriction
(No_Enumeration_Maps
, N
);
3591 Resolve
(E1
, P_Base_Type
);
3593 Validate_Non_Static_Attribute_Function_Call
;
3595 -- Check restriction No_Fixed_IO. Note the check of Comes_From_Source
3596 -- to avoid giving a duplicate message for Img expanded into Image.
3598 if Restriction_Check_Required
(No_Fixed_IO
)
3599 and then Comes_From_Source
(N
)
3600 and then Is_Fixed_Point_Type
(P_Type
)
3602 Check_Restriction
(No_Fixed_IO
, P
);
3610 when Attribute_Img
=> Img
:
3613 Set_Etype
(N
, Standard_String
);
3615 if not Is_Scalar_Type
(P_Type
)
3616 or else (Is_Entity_Name
(P
) and then Is_Type
(Entity
(P
)))
3619 ("prefix of % attribute must be scalar object name");
3624 -- Check restriction No_Fixed_IO
3626 if Restriction_Check_Required
(No_Fixed_IO
)
3627 and then Is_Fixed_Point_Type
(P_Type
)
3629 Check_Restriction
(No_Fixed_IO
, P
);
3637 when Attribute_Input
=>
3639 Check_Stream_Attribute
(TSS_Stream_Input
);
3640 Set_Etype
(N
, P_Base_Type
);
3646 when Attribute_Integer_Value
=>
3649 Resolve
(E1
, Any_Fixed
);
3651 -- Signal an error if argument type is not a specific fixed-point
3652 -- subtype. An error has been signalled already if the argument
3653 -- was not of a fixed-point type.
3655 if Etype
(E1
) = Any_Fixed
and then not Error_Posted
(E1
) then
3656 Error_Attr
("argument of % must be of a fixed-point type", E1
);
3659 Set_Etype
(N
, P_Base_Type
);
3665 when Attribute_Invalid_Value
=>
3668 Set_Etype
(N
, P_Base_Type
);
3669 Invalid_Value_Used
:= True;
3675 when Attribute_Large
=>
3678 Set_Etype
(N
, Universal_Real
);
3684 when Attribute_Last
=>
3685 Check_Array_Or_Scalar_Type
;
3686 Bad_Attribute_For_Predicate
;
3692 when Attribute_Last_Bit
=>
3694 Set_Etype
(N
, Universal_Integer
);
3700 when Attribute_Last_Valid
=>
3701 Check_First_Last_Valid
;
3702 Set_Etype
(N
, P_Type
);
3708 when Attribute_Leading_Part
=>
3709 Check_Floating_Point_Type_2
;
3710 Set_Etype
(N
, P_Base_Type
);
3711 Resolve
(E1
, P_Base_Type
);
3712 Resolve
(E2
, Any_Integer
);
3718 when Attribute_Length
=>
3720 Set_Etype
(N
, Universal_Integer
);
3726 when Attribute_Library_Level
=>
3729 if not Is_Entity_Name
(P
) then
3730 Error_Attr_P
("prefix of % attribute must be an entity name");
3733 if not Inside_A_Generic
then
3734 Set_Boolean_Result
(N
,
3735 Is_Library_Level_Entity
(Entity
(P
)));
3738 Set_Etype
(N
, Standard_Boolean
);
3744 when Attribute_Lock_Free
=>
3746 Set_Etype
(N
, Standard_Boolean
);
3748 if not Is_Protected_Type
(P_Type
) then
3750 ("prefix of % attribute must be a protected object");
3757 when Attribute_Loop_Entry
=> Loop_Entry
: declare
3758 procedure Check_References_In_Prefix
(Loop_Id
: Entity_Id
);
3759 -- Inspect the prefix for any uses of entities declared within the
3760 -- related loop. Loop_Id denotes the loop identifier.
3762 --------------------------------
3763 -- Check_References_In_Prefix --
3764 --------------------------------
3766 procedure Check_References_In_Prefix
(Loop_Id
: Entity_Id
) is
3767 Loop_Decl
: constant Node_Id
:= Label_Construct
(Parent
(Loop_Id
));
3769 function Check_Reference
(Nod
: Node_Id
) return Traverse_Result
;
3770 -- Determine whether a reference mentions an entity declared
3771 -- within the related loop.
3773 function Declared_Within
(Nod
: Node_Id
) return Boolean;
3774 -- Determine whether Nod appears in the subtree of Loop_Decl
3776 ---------------------
3777 -- Check_Reference --
3778 ---------------------
3780 function Check_Reference
(Nod
: Node_Id
) return Traverse_Result
is
3782 if Nkind
(Nod
) = N_Identifier
3783 and then Present
(Entity
(Nod
))
3784 and then Declared_Within
(Declaration_Node
(Entity
(Nod
)))
3787 ("prefix of attribute % cannot reference local entities",
3793 end Check_Reference
;
3795 procedure Check_References
is new Traverse_Proc
(Check_Reference
);
3797 ---------------------
3798 -- Declared_Within --
3799 ---------------------
3801 function Declared_Within
(Nod
: Node_Id
) return Boolean is
3806 while Present
(Stmt
) loop
3807 if Stmt
= Loop_Decl
then
3810 -- Prevent the search from going too far
3812 elsif Is_Body_Or_Package_Declaration
(Stmt
) then
3816 Stmt
:= Parent
(Stmt
);
3820 end Declared_Within
;
3822 -- Start of processing for Check_Prefix_For_Local_References
3825 Check_References
(P
);
3826 end Check_References_In_Prefix
;
3830 Context
: constant Node_Id
:= Parent
(N
);
3832 Enclosing_Loop
: Node_Id
;
3833 Loop_Id
: Entity_Id
:= Empty
;
3836 Enclosing_Pragma
: Node_Id
:= Empty
;
3838 -- Start of processing for Loop_Entry
3843 -- Set the type of the attribute now to ensure the successfull
3844 -- continuation of analysis even if the attribute is misplaced.
3846 Set_Etype
(Attr
, P_Type
);
3848 -- Attribute 'Loop_Entry may appear in several flavors:
3850 -- * Prefix'Loop_Entry - in this form, the attribute applies to the
3851 -- nearest enclosing loop.
3853 -- * Prefix'Loop_Entry (Expr) - depending on what Expr denotes, the
3854 -- attribute may be related to a loop denoted by label Expr or
3855 -- the prefix may denote an array object and Expr may act as an
3856 -- indexed component.
3858 -- * Prefix'Loop_Entry (Expr1, ..., ExprN) - the attribute applies
3859 -- to the nearest enclosing loop, all expressions are part of
3860 -- an indexed component.
3862 -- * Prefix'Loop_Entry (Expr) (...) (...) - depending on what Expr
3863 -- denotes, the attribute may be related to a loop denoted by
3864 -- label Expr or the prefix may denote a multidimensional array
3865 -- array object and Expr along with the rest of the expressions
3866 -- may act as indexed components.
3868 -- Regardless of variations, the attribute reference does not have an
3869 -- expression list. Instead, all available expressions are stored as
3870 -- indexed components.
3872 -- When the attribute is part of an indexed component, find the first
3873 -- expression as it will determine the semantics of 'Loop_Entry.
3875 if Nkind
(Context
) = N_Indexed_Component
then
3876 E1
:= First
(Expressions
(Context
));
3879 -- The attribute reference appears in the following form:
3881 -- Prefix'Loop_Entry (Exp1, Expr2, ..., ExprN) [(...)]
3883 -- In this case, the loop name is omitted and no rewriting is
3886 if Present
(E2
) then
3889 -- The form of the attribute is:
3891 -- Prefix'Loop_Entry (Expr) [(...)]
3893 -- If Expr denotes a loop entry, the whole attribute and indexed
3894 -- component will have to be rewritten to reflect this relation.
3897 pragma Assert
(Present
(E1
));
3899 -- Do not expand the expression as it may have side effects.
3900 -- Simply preanalyze to determine whether it is a loop name or
3903 Preanalyze_And_Resolve
(E1
);
3905 if Is_Entity_Name
(E1
)
3906 and then Present
(Entity
(E1
))
3907 and then Ekind
(Entity
(E1
)) = E_Loop
3909 Loop_Id
:= Entity
(E1
);
3911 -- Transform the attribute and enclosing indexed component
3913 Set_Expressions
(N
, Expressions
(Context
));
3914 Rewrite
(Context
, N
);
3915 Set_Etype
(Context
, P_Type
);
3922 -- The prefix must denote an object
3924 if not Is_Object_Reference
(P
) then
3925 Error_Attr_P
("prefix of attribute % must denote an object");
3928 -- The prefix cannot be of a limited type because the expansion of
3929 -- Loop_Entry must create a constant initialized by the evaluated
3932 if Is_Limited_View
(Etype
(P
)) then
3933 Error_Attr_P
("prefix of attribute % cannot be limited");
3936 -- Climb the parent chain to verify the location of the attribute and
3937 -- find the enclosing loop.
3940 while Present
(Stmt
) loop
3942 -- Locate the corresponding enclosing pragma. Note that in the
3943 -- case of Assert[And_Cut] and Assume, we have already checked
3944 -- that the pragma appears in an appropriate loop location.
3946 if Nkind
(Original_Node
(Stmt
)) = N_Pragma
3947 and then Nam_In
(Pragma_Name
(Original_Node
(Stmt
)),
3948 Name_Loop_Invariant
,
3951 Name_Assert_And_Cut
,
3954 Enclosing_Pragma
:= Original_Node
(Stmt
);
3956 -- Locate the enclosing loop (if any). Note that Ada 2012 array
3957 -- iteration may be expanded into several nested loops, we are
3958 -- interested in the outermost one which has the loop identifier.
3960 elsif Nkind
(Stmt
) = N_Loop_Statement
3961 and then Present
(Identifier
(Stmt
))
3963 Enclosing_Loop
:= Stmt
;
3965 -- The original attribute reference may lack a loop name. Use
3966 -- the name of the enclosing loop because it is the related
3969 if No
(Loop_Id
) then
3970 Loop_Id
:= Entity
(Identifier
(Enclosing_Loop
));
3975 -- Prevent the search from going too far
3977 elsif Is_Body_Or_Package_Declaration
(Stmt
) then
3981 Stmt
:= Parent
(Stmt
);
3984 -- Loop_Entry must appear within a Loop_Assertion pragma (Assert,
3985 -- Assert_And_Cut, Assume count as loop assertion pragmas for this
3986 -- purpose if they appear in an appropriate location in a loop,
3987 -- which was already checked by the top level pragma circuit).
3989 if No
(Enclosing_Pragma
) then
3990 Error_Attr
("attribute% must appear within appropriate pragma", N
);
3993 -- A Loop_Entry that applies to a given loop statement must not
3994 -- appear within a body of accept statement, if this construct is
3995 -- itself enclosed by the given loop statement.
3997 for Index
in reverse 0 .. Scope_Stack
.Last
loop
3998 Scop
:= Scope_Stack
.Table
(Index
).Entity
;
4000 if Ekind
(Scop
) = E_Loop
and then Scop
= Loop_Id
then
4002 elsif Ekind_In
(Scop
, E_Block
, E_Loop
, E_Return_Statement
) then
4006 ("attribute % cannot appear in body or accept statement", N
);
4011 -- The prefix cannot mention entities declared within the related
4012 -- loop because they will not be visible once the prefix is moved
4013 -- outside the loop.
4015 Check_References_In_Prefix
(Loop_Id
);
4017 -- The prefix must denote a static entity if the pragma does not
4018 -- apply to the innermost enclosing loop statement, or if it appears
4019 -- within a potentially unevaluated epxression.
4021 if Is_Entity_Name
(P
)
4022 or else Nkind
(Parent
(P
)) = N_Object_Renaming_Declaration
4026 elsif Present
(Enclosing_Loop
)
4027 and then Entity
(Identifier
(Enclosing_Loop
)) /= Loop_Id
4030 ("prefix of attribute % that applies to outer loop must denote "
4033 elsif Is_Potentially_Unevaluated
(P
) then
4037 -- Replace the Loop_Entry attribute reference by its prefix if the
4038 -- related pragma is ignored. This transformation is OK with respect
4039 -- to typing because Loop_Entry's type is that of its prefix. This
4040 -- early transformation also avoids the generation of a useless loop
4043 if Is_Ignored
(Enclosing_Pragma
) then
4044 Rewrite
(N
, Relocate_Node
(P
));
4047 Preanalyze_And_Resolve
(P
);
4054 when Attribute_Machine
=>
4055 Check_Floating_Point_Type_1
;
4056 Set_Etype
(N
, P_Base_Type
);
4057 Resolve
(E1
, P_Base_Type
);
4063 when Attribute_Machine_Emax
=>
4064 Check_Floating_Point_Type_0
;
4065 Set_Etype
(N
, Universal_Integer
);
4071 when Attribute_Machine_Emin
=>
4072 Check_Floating_Point_Type_0
;
4073 Set_Etype
(N
, Universal_Integer
);
4075 ----------------------
4076 -- Machine_Mantissa --
4077 ----------------------
4079 when Attribute_Machine_Mantissa
=>
4080 Check_Floating_Point_Type_0
;
4081 Set_Etype
(N
, Universal_Integer
);
4083 -----------------------
4084 -- Machine_Overflows --
4085 -----------------------
4087 when Attribute_Machine_Overflows
=>
4090 Set_Etype
(N
, Standard_Boolean
);
4096 when Attribute_Machine_Radix
=>
4099 Set_Etype
(N
, Universal_Integer
);
4101 ----------------------
4102 -- Machine_Rounding --
4103 ----------------------
4105 when Attribute_Machine_Rounding
=>
4106 Check_Floating_Point_Type_1
;
4107 Set_Etype
(N
, P_Base_Type
);
4108 Resolve
(E1
, P_Base_Type
);
4110 --------------------
4111 -- Machine_Rounds --
4112 --------------------
4114 when Attribute_Machine_Rounds
=>
4117 Set_Etype
(N
, Standard_Boolean
);
4123 when Attribute_Machine_Size
=>
4126 Check_Not_Incomplete_Type
;
4127 Set_Etype
(N
, Universal_Integer
);
4133 when Attribute_Mantissa
=>
4136 Set_Etype
(N
, Universal_Integer
);
4142 when Attribute_Max
=>
4145 ----------------------------------
4146 -- Max_Alignment_For_Allocation --
4147 ----------------------------------
4149 when Attribute_Max_Size_In_Storage_Elements
=>
4150 Max_Alignment_For_Allocation_Max_Size_In_Storage_Elements
;
4152 ----------------------------------
4153 -- Max_Size_In_Storage_Elements --
4154 ----------------------------------
4156 when Attribute_Max_Alignment_For_Allocation
=>
4157 Max_Alignment_For_Allocation_Max_Size_In_Storage_Elements
;
4159 -----------------------
4160 -- Maximum_Alignment --
4161 -----------------------
4163 when Attribute_Maximum_Alignment
=>
4164 Standard_Attribute
(Ttypes
.Maximum_Alignment
);
4166 --------------------
4167 -- Mechanism_Code --
4168 --------------------
4170 when Attribute_Mechanism_Code
=>
4171 if not Is_Entity_Name
(P
)
4172 or else not Is_Subprogram
(Entity
(P
))
4174 Error_Attr_P
("prefix of % attribute must be subprogram");
4177 Check_Either_E0_Or_E1
;
4179 if Present
(E1
) then
4180 Resolve
(E1
, Any_Integer
);
4181 Set_Etype
(E1
, Standard_Integer
);
4183 if not Is_OK_Static_Expression
(E1
) then
4184 Flag_Non_Static_Expr
4185 ("expression for parameter number must be static!", E1
);
4188 elsif UI_To_Int
(Intval
(E1
)) > Number_Formals
(Entity
(P
))
4189 or else UI_To_Int
(Intval
(E1
)) < 0
4191 Error_Attr
("invalid parameter number for % attribute", E1
);
4195 Set_Etype
(N
, Universal_Integer
);
4201 when Attribute_Min
=>
4208 when Attribute_Mod
=>
4210 -- Note: this attribute is only allowed in Ada 2005 mode, but
4211 -- we do not need to test that here, since Mod is only recognized
4212 -- as an attribute name in Ada 2005 mode during the parse.
4215 Check_Modular_Integer_Type
;
4216 Resolve
(E1
, Any_Integer
);
4217 Set_Etype
(N
, P_Base_Type
);
4223 when Attribute_Model
=>
4224 Check_Floating_Point_Type_1
;
4225 Set_Etype
(N
, P_Base_Type
);
4226 Resolve
(E1
, P_Base_Type
);
4232 when Attribute_Model_Emin
=>
4233 Check_Floating_Point_Type_0
;
4234 Set_Etype
(N
, Universal_Integer
);
4240 when Attribute_Model_Epsilon
=>
4241 Check_Floating_Point_Type_0
;
4242 Set_Etype
(N
, Universal_Real
);
4244 --------------------
4245 -- Model_Mantissa --
4246 --------------------
4248 when Attribute_Model_Mantissa
=>
4249 Check_Floating_Point_Type_0
;
4250 Set_Etype
(N
, Universal_Integer
);
4256 when Attribute_Model_Small
=>
4257 Check_Floating_Point_Type_0
;
4258 Set_Etype
(N
, Universal_Real
);
4264 when Attribute_Modulus
=>
4266 Check_Modular_Integer_Type
;
4267 Set_Etype
(N
, Universal_Integer
);
4269 --------------------
4270 -- Null_Parameter --
4271 --------------------
4273 when Attribute_Null_Parameter
=> Null_Parameter
: declare
4274 Parnt
: constant Node_Id
:= Parent
(N
);
4275 GParnt
: constant Node_Id
:= Parent
(Parnt
);
4277 procedure Bad_Null_Parameter
(Msg
: String);
4278 -- Used if bad Null parameter attribute node is found. Issues
4279 -- given error message, and also sets the type to Any_Type to
4280 -- avoid blowups later on from dealing with a junk node.
4282 procedure Must_Be_Imported
(Proc_Ent
: Entity_Id
);
4283 -- Called to check that Proc_Ent is imported subprogram
4285 ------------------------
4286 -- Bad_Null_Parameter --
4287 ------------------------
4289 procedure Bad_Null_Parameter
(Msg
: String) is
4291 Error_Msg_N
(Msg
, N
);
4292 Set_Etype
(N
, Any_Type
);
4293 end Bad_Null_Parameter
;
4295 ----------------------
4296 -- Must_Be_Imported --
4297 ----------------------
4299 procedure Must_Be_Imported
(Proc_Ent
: Entity_Id
) is
4300 Pent
: constant Entity_Id
:= Ultimate_Alias
(Proc_Ent
);
4303 -- Ignore check if procedure not frozen yet (we will get
4304 -- another chance when the default parameter is reanalyzed)
4306 if not Is_Frozen
(Pent
) then
4309 elsif not Is_Imported
(Pent
) then
4311 ("Null_Parameter can only be used with imported subprogram");
4316 end Must_Be_Imported
;
4318 -- Start of processing for Null_Parameter
4323 Set_Etype
(N
, P_Type
);
4325 -- Case of attribute used as default expression
4327 if Nkind
(Parnt
) = N_Parameter_Specification
then
4328 Must_Be_Imported
(Defining_Entity
(GParnt
));
4330 -- Case of attribute used as actual for subprogram (positional)
4332 elsif Nkind
(Parnt
) in N_Subprogram_Call
4333 and then Is_Entity_Name
(Name
(Parnt
))
4335 Must_Be_Imported
(Entity
(Name
(Parnt
)));
4337 -- Case of attribute used as actual for subprogram (named)
4339 elsif Nkind
(Parnt
) = N_Parameter_Association
4340 and then Nkind
(GParnt
) in N_Subprogram_Call
4341 and then Is_Entity_Name
(Name
(GParnt
))
4343 Must_Be_Imported
(Entity
(Name
(GParnt
)));
4345 -- Not an allowed case
4349 ("Null_Parameter must be actual or default parameter");
4357 when Attribute_Object_Size
=>
4360 Check_Not_Incomplete_Type
;
4361 Set_Etype
(N
, Universal_Integer
);
4367 when Attribute_Old
=> Old
: declare
4368 procedure Check_References_In_Prefix
(Subp_Id
: Entity_Id
);
4369 -- Inspect the contents of the prefix and detect illegal uses of a
4370 -- nested 'Old, attribute 'Result or a use of an entity declared in
4371 -- the related postcondition expression. Subp_Id is the subprogram to
4372 -- which the related postcondition applies.
4374 procedure Check_Use_In_Contract_Cases
(Prag
: Node_Id
);
4375 -- Perform various semantic checks related to the placement of the
4376 -- attribute in pragma Contract_Cases.
4378 procedure Check_Use_In_Test_Case
(Prag
: Node_Id
);
4379 -- Perform various semantic checks related to the placement of the
4380 -- attribute in pragma Contract_Cases.
4382 --------------------------------
4383 -- Check_References_In_Prefix --
4384 --------------------------------
4386 procedure Check_References_In_Prefix
(Subp_Id
: Entity_Id
) is
4387 function Check_Reference
(Nod
: Node_Id
) return Traverse_Result
;
4388 -- Detect attribute 'Old, attribute 'Result of a use of an entity
4389 -- and perform the appropriate semantic check.
4391 ---------------------
4392 -- Check_Reference --
4393 ---------------------
4395 function Check_Reference
(Nod
: Node_Id
) return Traverse_Result
is
4397 -- Attributes 'Old and 'Result cannot appear in the prefix of
4398 -- another attribute 'Old.
4400 if Nkind
(Nod
) = N_Attribute_Reference
4401 and then Nam_In
(Attribute_Name
(Nod
), Name_Old
,
4404 Error_Msg_Name_1
:= Attribute_Name
(Nod
);
4405 Error_Msg_Name_2
:= Name_Old
;
4407 ("attribute % cannot appear in the prefix of attribute %",
4411 -- Entities mentioned within the prefix of attribute 'Old must
4412 -- be global to the related postcondition. If this is not the
4413 -- case, then the scope of the local entity is nested within
4414 -- that of the subprogram.
4416 elsif Nkind
(Nod
) = N_Identifier
4417 and then Present
(Entity
(Nod
))
4418 and then Scope_Within
(Scope
(Entity
(Nod
)), Subp_Id
)
4421 ("prefix of attribute % cannot reference local entities",
4427 end Check_Reference
;
4429 procedure Check_References
is new Traverse_Proc
(Check_Reference
);
4431 -- Start of processing for Check_References_In_Prefix
4434 Check_References
(P
);
4435 end Check_References_In_Prefix
;
4437 ---------------------------------
4438 -- Check_Use_In_Contract_Cases --
4439 ---------------------------------
4441 procedure Check_Use_In_Contract_Cases
(Prag
: Node_Id
) is
4442 Cases
: constant Node_Id
:=
4444 (First
(Pragma_Argument_Associations
(Prag
)));
4448 -- Climb the parent chain to reach the top of the expression where
4449 -- attribute 'Old resides.
4452 while Parent
(Parent
(Expr
)) /= Cases
loop
4453 Expr
:= Parent
(Expr
);
4456 -- Ensure that the obtained expression is the consequence of a
4457 -- contract case as this is the only postcondition-like part of
4458 -- the pragma. Otherwise, attribute 'Old appears in the condition
4459 -- of a contract case. Emit an error since this is not a
4460 -- postcondition-like context. (SPARK RM 6.1.3(2))
4462 if Expr
/= Expression
(Parent
(Expr
)) then
4464 ("attribute % cannot appear in the condition "
4465 & "of a contract case", P
);
4467 end Check_Use_In_Contract_Cases
;
4469 ----------------------------
4470 -- Check_Use_In_Test_Case --
4471 ----------------------------
4473 procedure Check_Use_In_Test_Case
(Prag
: Node_Id
) is
4474 Ensures
: constant Node_Id
:= Get_Ensures_From_CTC_Pragma
(Prag
);
4478 -- Climb the parent chain to reach the top of the Ensures part of
4479 -- pragma Test_Case.
4482 while Expr
/= Prag
loop
4483 if Expr
= Ensures
then
4487 Expr
:= Parent
(Expr
);
4490 -- If we get there, then attribute 'Old appears in the requires
4491 -- expression of pragma Test_Case which is not a postcondition-
4495 ("attribute % cannot appear in the requires expression of a "
4497 end Check_Use_In_Test_Case
;
4502 -- The enclosing scope, excluding loops for quantified expressions.
4503 -- During analysis, it is the postcondition subprogram. During
4504 -- pre-analysis, it is the scope of the subprogram declaration.
4507 -- During pre-analysis, Prag is the enclosing pragma node if any
4509 -- Start of processing for Old
4514 -- Find enclosing scopes, excluding loops
4516 CS
:= Current_Scope
;
4517 while Ekind
(CS
) = E_Loop
loop
4521 -- A Contract_Cases, Postcondition or Test_Case pragma is in the
4522 -- process of being preanalyzed. Perform the semantic checks now
4523 -- before the pragma is relocated and/or expanded.
4525 -- For a generic subprogram, postconditions are preanalyzed as well
4526 -- for name capture, and still appear within an aspect spec.
4528 if In_Spec_Expression
or Inside_A_Generic
then
4530 while Present
(Prag
)
4531 and then not Nkind_In
(Prag
, N_Aspect_Specification
,
4532 N_Function_Specification
,
4534 N_Procedure_Specification
,
4537 Prag
:= Parent
(Prag
);
4540 -- In ASIS mode, the aspect itself is analyzed, in addition to the
4541 -- corresponding pragma. Don't issue errors when analyzing aspect.
4543 if Nkind
(Prag
) = N_Aspect_Specification
4544 and then Chars
(Identifier
(Prag
)) = Name_Post
4548 -- In all other cases the related context must be a pragma
4550 elsif Nkind
(Prag
) /= N_Pragma
then
4551 Error_Attr
("% attribute can only appear in postcondition", P
);
4553 -- Verify the placement of the attribute with respect to the
4557 case Get_Pragma_Id
(Prag
) is
4558 when Pragma_Contract_Cases
=>
4559 Check_Use_In_Contract_Cases
(Prag
);
4561 when Pragma_Postcondition | Pragma_Refined_Post
=>
4564 when Pragma_Test_Case
=>
4565 Check_Use_In_Test_Case
(Prag
);
4569 ("% attribute can only appear in postcondition", P
);
4573 -- Check the legality of attribute 'Old when it appears inside pragma
4574 -- Refined_Post. These specialized checks are required only when code
4575 -- generation is disabled. In the general case pragma Refined_Post is
4576 -- transformed into pragma Check by Process_PPCs which in turn is
4577 -- relocated to procedure _Postconditions. From then on the legality
4578 -- of 'Old is determined as usual.
4580 elsif not Expander_Active
and then In_Refined_Post
then
4581 Preanalyze_And_Resolve
(P
);
4582 Check_References_In_Prefix
(CS
);
4583 P_Type
:= Etype
(P
);
4584 Set_Etype
(N
, P_Type
);
4586 if Is_Limited_Type
(P_Type
) then
4587 Error_Attr
("attribute % cannot apply to limited objects", P
);
4590 if Is_Entity_Name
(P
)
4591 and then Is_Constant_Object
(Entity
(P
))
4594 ("??attribute Old applied to constant has no effect", P
);
4599 -- Body case, where we must be inside a generated _Postconditions
4600 -- procedure, or else the attribute use is definitely misplaced. The
4601 -- postcondition itself may have generated transient scopes, and is
4602 -- not necessarily the current one.
4605 while Present
(CS
) and then CS
/= Standard_Standard
loop
4606 if Chars
(CS
) = Name_uPostconditions
then
4613 if Chars
(CS
) /= Name_uPostconditions
then
4614 Error_Attr
("% attribute can only appear in postcondition", P
);
4618 -- If the attribute reference is generated for a Requires clause,
4619 -- then no expressions follow. Otherwise it is a primary, in which
4620 -- case, if expressions follow, the attribute reference must be an
4621 -- indexable object, so rewrite the node accordingly.
4623 if Present
(E1
) then
4625 Make_Indexed_Component
(Loc
,
4627 Make_Attribute_Reference
(Loc
,
4628 Prefix
=> Relocate_Node
(Prefix
(N
)),
4629 Attribute_Name
=> Name_Old
),
4630 Expressions
=> Expressions
(N
)));
4638 -- Prefix has not been analyzed yet, and its full analysis will take
4639 -- place during expansion (see below).
4641 Preanalyze_And_Resolve
(P
);
4642 Check_References_In_Prefix
(CS
);
4643 P_Type
:= Etype
(P
);
4644 Set_Etype
(N
, P_Type
);
4646 if Is_Limited_Type
(P_Type
) then
4647 Error_Attr
("attribute % cannot apply to limited objects", P
);
4650 if Is_Entity_Name
(P
)
4651 and then Is_Constant_Object
(Entity
(P
))
4654 ("??attribute Old applied to constant has no effect", P
);
4657 -- Check that the prefix of 'Old is an entity when it may be
4658 -- potentially unevaluated (6.1.1 (27/3)).
4661 and then Is_Potentially_Unevaluated
(N
)
4662 and then not Is_Entity_Name
(P
)
4667 -- The attribute appears within a pre/postcondition, but refers to
4668 -- an entity in the enclosing subprogram. If it is a component of
4669 -- a formal its expansion might generate actual subtypes that may
4670 -- be referenced in an inner context, and which must be elaborated
4671 -- within the subprogram itself. If the prefix includes a function
4672 -- call it may involve finalization actions that should only be
4673 -- inserted when the attribute has been rewritten as a declarations.
4674 -- As a result, if the prefix is not a simple name we create
4675 -- a declaration for it now, and insert it at the start of the
4676 -- enclosing subprogram. This is properly an expansion activity
4677 -- but it has to be performed now to prevent out-of-order issues.
4679 -- This expansion is both harmful and not needed in SPARK mode, since
4680 -- the formal verification backend relies on the types of nodes
4681 -- (hence is not robust w.r.t. a change to base type here), and does
4682 -- not suffer from the out-of-order issue described above. Thus, this
4683 -- expansion is skipped in SPARK mode.
4685 if not Is_Entity_Name
(P
) and then not GNATprove_Mode
then
4686 P_Type
:= Base_Type
(P_Type
);
4687 Set_Etype
(N
, P_Type
);
4688 Set_Etype
(P
, P_Type
);
4689 Analyze_Dimension
(N
);
4694 ----------------------
4695 -- Overlaps_Storage --
4696 ----------------------
4698 when Attribute_Overlaps_Storage
=>
4701 -- Both arguments must be objects of any type
4703 Analyze_And_Resolve
(P
);
4704 Analyze_And_Resolve
(E1
);
4705 Check_Object_Reference
(P
);
4706 Check_Object_Reference
(E1
);
4707 Set_Etype
(N
, Standard_Boolean
);
4713 when Attribute_Output
=>
4715 Check_Stream_Attribute
(TSS_Stream_Output
);
4716 Set_Etype
(N
, Standard_Void_Type
);
4717 Resolve
(N
, Standard_Void_Type
);
4723 when Attribute_Partition_ID
=> Partition_Id
:
4727 if P_Type
/= Any_Type
then
4728 if not Is_Library_Level_Entity
(Entity
(P
)) then
4730 ("prefix of % attribute must be library-level entity");
4732 -- The defining entity of prefix should not be declared inside a
4733 -- Pure unit. RM E.1(8). Is_Pure was set during declaration.
4735 elsif Is_Entity_Name
(P
)
4736 and then Is_Pure
(Entity
(P
))
4738 Error_Attr_P
("prefix of% attribute must not be declared pure");
4742 Set_Etype
(N
, Universal_Integer
);
4745 -------------------------
4746 -- Passed_By_Reference --
4747 -------------------------
4749 when Attribute_Passed_By_Reference
=>
4752 Set_Etype
(N
, Standard_Boolean
);
4758 when Attribute_Pool_Address
=>
4760 Set_Etype
(N
, RTE
(RE_Address
));
4766 when Attribute_Pos
=>
4767 Check_Discrete_Type
;
4770 if Is_Boolean_Type
(P_Type
) then
4771 Error_Msg_Name_1
:= Aname
;
4772 Error_Msg_Name_2
:= Chars
(P_Type
);
4773 Check_SPARK_Restriction
4774 ("attribute% is not allowed for type%", P
);
4777 Resolve
(E1
, P_Base_Type
);
4778 Set_Etype
(N
, Universal_Integer
);
4784 when Attribute_Position
=>
4786 Set_Etype
(N
, Universal_Integer
);
4792 when Attribute_Pred
=>
4796 if Is_Real_Type
(P_Type
) or else Is_Boolean_Type
(P_Type
) then
4797 Error_Msg_Name_1
:= Aname
;
4798 Error_Msg_Name_2
:= Chars
(P_Type
);
4799 Check_SPARK_Restriction
("attribute% is not allowed for type%", P
);
4802 Resolve
(E1
, P_Base_Type
);
4803 Set_Etype
(N
, P_Base_Type
);
4805 -- Since Pred works on the base type, we normally do no check for the
4806 -- floating-point case, since the base type is unconstrained. But we
4807 -- make an exception in Check_Float_Overflow mode.
4809 if Is_Floating_Point_Type
(P_Type
) then
4810 if Check_Float_Overflow
4811 and then not Range_Checks_Suppressed
(P_Base_Type
)
4813 Enable_Range_Check
(E1
);
4816 -- If not modular type, test for overflow check required
4819 if not Is_Modular_Integer_Type
(P_Type
)
4820 and then not Range_Checks_Suppressed
(P_Base_Type
)
4822 Enable_Range_Check
(E1
);
4830 -- Ada 2005 (AI-327): Dynamic ceiling priorities
4832 when Attribute_Priority
=>
4833 if Ada_Version
< Ada_2005
then
4834 Error_Attr
("% attribute is allowed only in Ada 2005 mode", P
);
4839 -- The prefix must be a protected object (AARM D.5.2 (2/2))
4843 if Is_Protected_Type
(Etype
(P
))
4844 or else (Is_Access_Type
(Etype
(P
))
4845 and then Is_Protected_Type
(Designated_Type
(Etype
(P
))))
4847 Resolve
(P
, Etype
(P
));
4849 Error_Attr_P
("prefix of % attribute must be a protected object");
4852 Set_Etype
(N
, Standard_Integer
);
4854 -- Must be called from within a protected procedure or entry of the
4855 -- protected object.
4862 while S
/= Etype
(P
)
4863 and then S
/= Standard_Standard
4868 if S
= Standard_Standard
then
4869 Error_Attr
("the attribute % is only allowed inside protected "
4874 Validate_Non_Static_Attribute_Function_Call
;
4880 when Attribute_Range
=>
4881 Check_Array_Or_Scalar_Type
;
4882 Bad_Attribute_For_Predicate
;
4884 if Ada_Version
= Ada_83
4885 and then Is_Scalar_Type
(P_Type
)
4886 and then Comes_From_Source
(N
)
4889 ("(Ada 83) % attribute not allowed for scalar type", P
);
4896 when Attribute_Result
=> Result
: declare
4898 -- The enclosing scope, excluding loops for quantified expressions
4901 -- During analysis, CS is the postcondition subprogram and PS the
4902 -- source subprogram to which the postcondition applies. During
4903 -- pre-analysis, CS is the scope of the subprogram declaration.
4906 -- During pre-analysis, Prag is the enclosing pragma node if any
4909 -- Find the proper enclosing scope
4911 CS
:= Current_Scope
;
4912 while Present
(CS
) loop
4914 -- Skip generated loops
4916 if Ekind
(CS
) = E_Loop
then
4919 -- Skip the special _Parent scope generated to capture references
4920 -- to formals during the process of subprogram inlining.
4922 elsif Ekind
(CS
) = E_Function
4923 and then Chars
(CS
) = Name_uParent
4933 -- If the enclosing subprogram is always inlined, the enclosing
4934 -- postcondition will not be propagated to the expanded call.
4936 if not In_Spec_Expression
4937 and then Has_Pragma_Inline_Always
(PS
)
4938 and then Warn_On_Redundant_Constructs
4941 ("postconditions on inlined functions not enforced?r?", N
);
4944 -- If we are in the scope of a function and in Spec_Expression mode,
4945 -- this is likely the prescan of the postcondition (or contract case,
4946 -- or test case) pragma, and we just set the proper type. If there is
4947 -- an error it will be caught when the real Analyze call is done.
4949 if Ekind
(CS
) = E_Function
4950 and then In_Spec_Expression
4954 if Chars
(CS
) /= Chars
(P
) then
4955 Error_Msg_Name_1
:= Name_Result
;
4958 ("incorrect prefix for % attribute, expected &", P
, CS
);
4962 -- Check in postcondition, Test_Case or Contract_Cases of function
4965 while Present
(Prag
)
4966 and then not Nkind_In
(Prag
, N_Pragma
,
4967 N_Function_Specification
,
4968 N_Aspect_Specification
,
4971 Prag
:= Parent
(Prag
);
4974 -- In ASIS mode, the aspect itself is analyzed, in addition to the
4975 -- corresponding pragma. Do not issue errors when analyzing the
4978 if Nkind
(Prag
) = N_Aspect_Specification
then
4981 -- Must have a pragma
4983 elsif Nkind
(Prag
) /= N_Pragma
then
4985 ("% attribute can only appear in postcondition of function",
4988 -- Processing depends on which pragma we have
4991 case Get_Pragma_Id
(Prag
) is
4993 when Pragma_Test_Case
=>
4995 Arg_Ens
: constant Node_Id
:=
4996 Get_Ensures_From_CTC_Pragma
(Prag
);
5001 while Arg
/= Prag
and then Arg
/= Arg_Ens
loop
5002 Arg
:= Parent
(Arg
);
5005 if Arg
/= Arg_Ens
then
5007 ("% attribute misplaced inside test case", P
);
5011 when Pragma_Contract_Cases
=>
5013 Aggr
: constant Node_Id
:=
5015 (Pragma_Argument_Associations
(Prag
)));
5021 and then Parent
(Parent
(Arg
)) /= Aggr
5023 Arg
:= Parent
(Arg
);
5026 -- At this point, Parent (Arg) should be a component
5027 -- association. Attribute Result is only allowed in
5028 -- the expression part of this association.
5030 if Nkind
(Parent
(Arg
)) /= N_Component_Association
5031 or else Arg
/= Expression
(Parent
(Arg
))
5034 ("% attribute misplaced inside contract cases",
5039 when Pragma_Postcondition | Pragma_Refined_Post
=>
5044 ("% attribute can only appear in postcondition "
5045 & "of function", P
);
5049 -- The attribute reference is a primary. If expressions follow,
5050 -- the attribute reference is really an indexable object, so
5051 -- rewrite and analyze as an indexed component.
5053 if Present
(E1
) then
5055 Make_Indexed_Component
(Loc
,
5057 Make_Attribute_Reference
(Loc
,
5058 Prefix
=> Relocate_Node
(Prefix
(N
)),
5059 Attribute_Name
=> Name_Result
),
5060 Expressions
=> Expressions
(N
)));
5065 Set_Etype
(N
, Etype
(CS
));
5067 -- If several functions with that name are visible, the intended
5068 -- one is the current scope.
5070 if Is_Overloaded
(P
) then
5072 Set_Is_Overloaded
(P
, False);
5075 -- Check the legality of attribute 'Result when it appears inside
5076 -- pragma Refined_Post. These specialized checks are required only
5077 -- when code generation is disabled. In the general case pragma
5078 -- Refined_Post is transformed into pragma Check by Process_PPCs
5079 -- which in turn is relocated to procedure _Postconditions. From
5080 -- then on the legality of 'Result is determined as usual.
5082 elsif not Expander_Active
and then In_Refined_Post
then
5083 PS
:= Current_Scope
;
5085 -- The prefix denotes the proper related function
5087 if Is_Entity_Name
(P
)
5088 and then Ekind
(Entity
(P
)) = E_Function
5089 and then Entity
(P
) = PS
5094 Error_Msg_Name_2
:= Chars
(PS
);
5095 Error_Attr
("incorrect prefix for % attribute, expected %", P
);
5098 Set_Etype
(N
, Etype
(PS
));
5100 -- Body case, where we must be inside a generated _Postconditions
5101 -- procedure, and the prefix must be on the scope stack, or else the
5102 -- attribute use is definitely misplaced. The postcondition itself
5103 -- may have generated transient scopes, and is not necessarily the
5107 while Present
(CS
) and then CS
/= Standard_Standard
loop
5108 if Chars
(CS
) = Name_uPostconditions
then
5117 if Chars
(CS
) = Name_uPostconditions
5118 and then Ekind
(PS
) = E_Function
5122 if Nkind_In
(P
, N_Identifier
, N_Operator_Symbol
)
5123 and then Chars
(P
) = Chars
(PS
)
5127 -- Within an instance, the prefix designates the local renaming
5128 -- of the original generic.
5130 elsif Is_Entity_Name
(P
)
5131 and then Ekind
(Entity
(P
)) = E_Function
5132 and then Present
(Alias
(Entity
(P
)))
5133 and then Chars
(Alias
(Entity
(P
))) = Chars
(PS
)
5138 Error_Msg_Name_2
:= Chars
(PS
);
5140 ("incorrect prefix for % attribute, expected %", P
);
5143 Rewrite
(N
, Make_Identifier
(Sloc
(N
), Name_uResult
));
5144 Analyze_And_Resolve
(N
, Etype
(PS
));
5148 ("% attribute can only appear in postcondition of function",
5158 when Attribute_Range_Length
=>
5160 Check_Discrete_Type
;
5161 Set_Etype
(N
, Universal_Integer
);
5167 when Attribute_Read
=>
5169 Check_Stream_Attribute
(TSS_Stream_Read
);
5170 Set_Etype
(N
, Standard_Void_Type
);
5171 Resolve
(N
, Standard_Void_Type
);
5172 Note_Possible_Modification
(E2
, Sure
=> True);
5178 when Attribute_Ref
=>
5182 if Nkind
(P
) /= N_Expanded_Name
5183 or else not Is_RTE
(P_Type
, RE_Address
)
5185 Error_Attr_P
("prefix of % attribute must be System.Address");
5188 Analyze_And_Resolve
(E1
, Any_Integer
);
5189 Set_Etype
(N
, RTE
(RE_Address
));
5195 when Attribute_Remainder
=>
5196 Check_Floating_Point_Type_2
;
5197 Set_Etype
(N
, P_Base_Type
);
5198 Resolve
(E1
, P_Base_Type
);
5199 Resolve
(E2
, P_Base_Type
);
5201 ---------------------
5202 -- Restriction_Set --
5203 ---------------------
5205 when Attribute_Restriction_Set
=> Restriction_Set
: declare
5208 Unam
: Unit_Name_Type
;
5213 Check_System_Prefix
;
5215 -- No_Dependence case
5217 if Nkind
(E1
) = N_Parameter_Association
then
5218 pragma Assert
(Chars
(Selector_Name
(E1
)) = Name_No_Dependence
);
5219 U
:= Explicit_Actual_Parameter
(E1
);
5221 if not OK_No_Dependence_Unit_Name
(U
) then
5222 Set_Boolean_Result
(N
, False);
5226 -- See if there is an entry already in the table. That's the
5227 -- case in which we can return True.
5229 for J
in No_Dependences
.First
.. No_Dependences
.Last
loop
5230 if Designate_Same_Unit
(U
, No_Dependences
.Table
(J
).Unit
)
5231 and then No_Dependences
.Table
(J
).Warn
= False
5233 Set_Boolean_Result
(N
, True);
5238 -- If not in the No_Dependence table, result is False
5240 Set_Boolean_Result
(N
, False);
5242 -- In this case, we must ensure that the binder will reject any
5243 -- other unit in the partition that sets No_Dependence for this
5244 -- unit. We do that by making an entry in the special table kept
5245 -- for this purpose (if the entry is not there already).
5247 Unam
:= Get_Spec_Name
(Get_Unit_Name
(U
));
5249 for J
in Restriction_Set_Dependences
.First
..
5250 Restriction_Set_Dependences
.Last
5252 if Restriction_Set_Dependences
.Table
(J
) = Unam
then
5257 Restriction_Set_Dependences
.Append
(Unam
);
5259 -- Normal restriction case
5262 if Nkind
(E1
) /= N_Identifier
then
5263 Set_Boolean_Result
(N
, False);
5264 Error_Attr
("attribute % requires restriction identifier", E1
);
5267 R
:= Get_Restriction_Id
(Process_Restriction_Synonyms
(E1
));
5269 if R
= Not_A_Restriction_Id
then
5270 Set_Boolean_Result
(N
, False);
5271 Error_Msg_Node_1
:= E1
;
5272 Error_Attr
("invalid restriction identifier &", E1
);
5274 elsif R
not in Partition_Boolean_Restrictions
then
5275 Set_Boolean_Result
(N
, False);
5276 Error_Msg_Node_1
:= E1
;
5278 ("& is not a boolean partition-wide restriction", E1
);
5281 if Restriction_Active
(R
) then
5282 Set_Boolean_Result
(N
, True);
5284 Check_Restriction
(R
, N
);
5285 Set_Boolean_Result
(N
, False);
5289 end Restriction_Set
;
5295 when Attribute_Round
=>
5297 Check_Decimal_Fixed_Point_Type
;
5298 Set_Etype
(N
, P_Base_Type
);
5300 -- Because the context is universal_real (3.5.10(12)) it is a
5301 -- legal context for a universal fixed expression. This is the
5302 -- only attribute whose functional description involves U_R.
5304 if Etype
(E1
) = Universal_Fixed
then
5306 Conv
: constant Node_Id
:= Make_Type_Conversion
(Loc
,
5307 Subtype_Mark
=> New_Occurrence_Of
(Universal_Real
, Loc
),
5308 Expression
=> Relocate_Node
(E1
));
5316 Resolve
(E1
, Any_Real
);
5322 when Attribute_Rounding
=>
5323 Check_Floating_Point_Type_1
;
5324 Set_Etype
(N
, P_Base_Type
);
5325 Resolve
(E1
, P_Base_Type
);
5331 when Attribute_Safe_Emax
=>
5332 Check_Floating_Point_Type_0
;
5333 Set_Etype
(N
, Universal_Integer
);
5339 when Attribute_Safe_First
=>
5340 Check_Floating_Point_Type_0
;
5341 Set_Etype
(N
, Universal_Real
);
5347 when Attribute_Safe_Large
=>
5350 Set_Etype
(N
, Universal_Real
);
5356 when Attribute_Safe_Last
=>
5357 Check_Floating_Point_Type_0
;
5358 Set_Etype
(N
, Universal_Real
);
5364 when Attribute_Safe_Small
=>
5367 Set_Etype
(N
, Universal_Real
);
5369 --------------------------
5370 -- Scalar_Storage_Order --
5371 --------------------------
5373 when Attribute_Scalar_Storage_Order
=> Scalar_Storage_Order
:
5375 Ent
: Entity_Id
:= Empty
;
5381 if not (Is_Record_Type
(P_Type
) or else Is_Array_Type
(P_Type
)) then
5383 -- In GNAT mode, the attribute applies to generic types as well
5384 -- as composite types, and for non-composite types always returns
5385 -- the default bit order for the target.
5387 if not (GNAT_Mode
and then Is_Generic_Type
(P_Type
))
5388 and then not In_Instance
5391 ("prefix of % attribute must be record or array type");
5393 elsif not Is_Generic_Type
(P_Type
) then
5394 if Bytes_Big_Endian
then
5395 Ent
:= RTE
(RE_High_Order_First
);
5397 Ent
:= RTE
(RE_Low_Order_First
);
5401 elsif Bytes_Big_Endian
xor Reverse_Storage_Order
(P_Type
) then
5402 Ent
:= RTE
(RE_High_Order_First
);
5405 Ent
:= RTE
(RE_Low_Order_First
);
5408 if Present
(Ent
) then
5409 Rewrite
(N
, New_Occurrence_Of
(Ent
, Loc
));
5412 Set_Etype
(N
, RTE
(RE_Bit_Order
));
5415 -- Reset incorrect indication of staticness
5417 Set_Is_Static_Expression
(N
, False);
5418 end Scalar_Storage_Order
;
5424 when Attribute_Scale
=>
5426 Check_Decimal_Fixed_Point_Type
;
5427 Set_Etype
(N
, Universal_Integer
);
5433 when Attribute_Scaling
=>
5434 Check_Floating_Point_Type_2
;
5435 Set_Etype
(N
, P_Base_Type
);
5436 Resolve
(E1
, P_Base_Type
);
5442 when Attribute_Signed_Zeros
=>
5443 Check_Floating_Point_Type_0
;
5444 Set_Etype
(N
, Standard_Boolean
);
5450 when Attribute_Size | Attribute_VADS_Size
=> Size
:
5454 -- If prefix is parameterless function call, rewrite and resolve
5457 if Is_Entity_Name
(P
)
5458 and then Ekind
(Entity
(P
)) = E_Function
5462 -- Similar processing for a protected function call
5464 elsif Nkind
(P
) = N_Selected_Component
5465 and then Ekind
(Entity
(Selector_Name
(P
))) = E_Function
5470 if Is_Object_Reference
(P
) then
5471 Check_Object_Reference
(P
);
5473 elsif Is_Entity_Name
(P
)
5474 and then (Is_Type
(Entity
(P
))
5475 or else Ekind
(Entity
(P
)) = E_Enumeration_Literal
)
5479 elsif Nkind
(P
) = N_Type_Conversion
5480 and then not Comes_From_Source
(P
)
5484 -- Some other compilers allow dubious use of X'???'Size
5486 elsif Relaxed_RM_Semantics
5487 and then Nkind
(P
) = N_Attribute_Reference
5492 Error_Attr_P
("invalid prefix for % attribute");
5495 Check_Not_Incomplete_Type
;
5497 Set_Etype
(N
, Universal_Integer
);
5504 when Attribute_Small
=>
5507 Set_Etype
(N
, Universal_Real
);
5513 when Attribute_Storage_Pool |
5514 Attribute_Simple_Storage_Pool
=> Storage_Pool
:
5518 if Is_Access_Type
(P_Type
) then
5519 if Ekind
(P_Type
) = E_Access_Subprogram_Type
then
5521 ("cannot use % attribute for access-to-subprogram type");
5524 -- Set appropriate entity
5526 if Present
(Associated_Storage_Pool
(Root_Type
(P_Type
))) then
5527 Set_Entity
(N
, Associated_Storage_Pool
(Root_Type
(P_Type
)));
5529 Set_Entity
(N
, RTE
(RE_Global_Pool_Object
));
5532 if Attr_Id
= Attribute_Storage_Pool
then
5533 if Present
(Get_Rep_Pragma
(Etype
(Entity
(N
)),
5534 Name_Simple_Storage_Pool_Type
))
5536 Error_Msg_Name_1
:= Aname
;
5537 Error_Msg_Warn
:= SPARK_Mode
/= On
;
5538 Error_Msg_N
("cannot use % attribute for type with simple "
5539 & "storage pool<<", N
);
5540 Error_Msg_N
("\Program_Error [<<", N
);
5543 (N
, Make_Raise_Program_Error
5544 (Sloc
(N
), Reason
=> PE_Explicit_Raise
));
5547 Set_Etype
(N
, Class_Wide_Type
(RTE
(RE_Root_Storage_Pool
)));
5549 -- In the Simple_Storage_Pool case, verify that the pool entity is
5550 -- actually of a simple storage pool type, and set the attribute's
5551 -- type to the pool object's type.
5554 if not Present
(Get_Rep_Pragma
(Etype
(Entity
(N
)),
5555 Name_Simple_Storage_Pool_Type
))
5558 ("cannot use % attribute for type without simple " &
5562 Set_Etype
(N
, Etype
(Entity
(N
)));
5565 -- Validate_Remote_Access_To_Class_Wide_Type for attribute
5566 -- Storage_Pool since this attribute is not defined for such
5567 -- types (RM E.2.3(22)).
5569 Validate_Remote_Access_To_Class_Wide_Type
(N
);
5572 Error_Attr_P
("prefix of % attribute must be access type");
5580 when Attribute_Storage_Size
=> Storage_Size
:
5584 if Is_Task_Type
(P_Type
) then
5585 Set_Etype
(N
, Universal_Integer
);
5587 -- Use with tasks is an obsolescent feature
5589 Check_Restriction
(No_Obsolescent_Features
, P
);
5591 elsif Is_Access_Type
(P_Type
) then
5592 if Ekind
(P_Type
) = E_Access_Subprogram_Type
then
5594 ("cannot use % attribute for access-to-subprogram type");
5597 if Is_Entity_Name
(P
)
5598 and then Is_Type
(Entity
(P
))
5601 Set_Etype
(N
, Universal_Integer
);
5603 -- Validate_Remote_Access_To_Class_Wide_Type for attribute
5604 -- Storage_Size since this attribute is not defined for
5605 -- such types (RM E.2.3(22)).
5607 Validate_Remote_Access_To_Class_Wide_Type
(N
);
5609 -- The prefix is allowed to be an implicit dereference of an
5610 -- access value designating a task.
5614 Set_Etype
(N
, Universal_Integer
);
5618 Error_Attr_P
("prefix of % attribute must be access or task type");
5626 when Attribute_Storage_Unit
=>
5627 Standard_Attribute
(Ttypes
.System_Storage_Unit
);
5633 when Attribute_Stream_Size
=>
5637 if Is_Entity_Name
(P
)
5638 and then Is_Elementary_Type
(Entity
(P
))
5640 Set_Etype
(N
, Universal_Integer
);
5642 Error_Attr_P
("invalid prefix for % attribute");
5649 when Attribute_Stub_Type
=>
5653 if Is_Remote_Access_To_Class_Wide_Type
(Base_Type
(P_Type
)) then
5655 -- For a real RACW [sub]type, use corresponding stub type
5657 if not Is_Generic_Type
(P_Type
) then
5660 (Corresponding_Stub_Type
(Base_Type
(P_Type
)), Loc
));
5662 -- For a generic type (that has been marked as an RACW using the
5663 -- Remote_Access_Type aspect or pragma), use a generic RACW stub
5664 -- type. Note that if the actual is not a remote access type, the
5665 -- instantiation will fail.
5668 -- Note: we go to the underlying type here because the view
5669 -- returned by RTE (RE_RACW_Stub_Type) might be incomplete.
5673 (Underlying_Type
(RTE
(RE_RACW_Stub_Type
)), Loc
));
5678 ("prefix of% attribute must be remote access to classwide");
5685 when Attribute_Succ
=>
5689 if Is_Real_Type
(P_Type
) or else Is_Boolean_Type
(P_Type
) then
5690 Error_Msg_Name_1
:= Aname
;
5691 Error_Msg_Name_2
:= Chars
(P_Type
);
5692 Check_SPARK_Restriction
("attribute% is not allowed for type%", P
);
5695 Resolve
(E1
, P_Base_Type
);
5696 Set_Etype
(N
, P_Base_Type
);
5698 -- Since Pred works on the base type, we normally do no check for the
5699 -- floating-point case, since the base type is unconstrained. But we
5700 -- make an exception in Check_Float_Overflow mode.
5702 if Is_Floating_Point_Type
(P_Type
) then
5703 if Check_Float_Overflow
5704 and then not Range_Checks_Suppressed
(P_Base_Type
)
5706 Enable_Range_Check
(E1
);
5709 -- If not modular type, test for overflow check required
5712 if not Is_Modular_Integer_Type
(P_Type
)
5713 and then not Range_Checks_Suppressed
(P_Base_Type
)
5715 Enable_Range_Check
(E1
);
5719 --------------------------------
5720 -- System_Allocator_Alignment --
5721 --------------------------------
5723 when Attribute_System_Allocator_Alignment
=>
5724 Standard_Attribute
(Ttypes
.System_Allocator_Alignment
);
5730 when Attribute_Tag
=> Tag
:
5735 if not Is_Tagged_Type
(P_Type
) then
5736 Error_Attr_P
("prefix of % attribute must be tagged");
5738 -- Next test does not apply to generated code why not, and what does
5739 -- the illegal reference mean???
5741 elsif Is_Object_Reference
(P
)
5742 and then not Is_Class_Wide_Type
(P_Type
)
5743 and then Comes_From_Source
(N
)
5746 ("% attribute can only be applied to objects " &
5747 "of class - wide type");
5750 -- The prefix cannot be an incomplete type. However, references to
5751 -- 'Tag can be generated when expanding interface conversions, and
5754 if Comes_From_Source
(N
) then
5755 Check_Not_Incomplete_Type
;
5758 -- Set appropriate type
5760 Set_Etype
(N
, RTE
(RE_Tag
));
5767 when Attribute_Target_Name
=> Target_Name
: declare
5768 TN
: constant String := Sdefault
.Target_Name
.all;
5772 Check_Standard_Prefix
;
5776 if TN
(TL
) = '/' or else TN
(TL
) = '\' then
5781 Make_String_Literal
(Loc
,
5782 Strval
=> TN
(TN
'First .. TL
)));
5783 Analyze_And_Resolve
(N
, Standard_String
);
5784 Set_Is_Static_Expression
(N
, True);
5791 when Attribute_Terminated
=>
5793 Set_Etype
(N
, Standard_Boolean
);
5800 when Attribute_To_Address
=> To_Address
: declare
5806 Check_System_Prefix
;
5808 Generate_Reference
(RTE
(RE_Address
), P
);
5809 Analyze_And_Resolve
(E1
, Any_Integer
);
5810 Set_Etype
(N
, RTE
(RE_Address
));
5812 if Is_Static_Expression
(E1
) then
5813 Set_Is_Static_Expression
(N
, True);
5816 -- OK static expression case, check range and set appropriate type
5818 if Is_OK_Static_Expression
(E1
) then
5819 Val
:= Expr_Value
(E1
);
5821 if Val
< -(2 ** UI_From_Int
(Standard
'Address_Size - 1))
5823 Val
> 2 ** UI_From_Int
(Standard
'Address_Size) - 1
5825 Error_Attr
("address value out of range for % attribute", E1
);
5828 -- In most cases the expression is a numeric literal or some other
5829 -- address expression, but if it is a declared constant it may be
5830 -- of a compatible type that must be left on the node.
5832 if Is_Entity_Name
(E1
) then
5835 -- Set type to universal integer if negative
5838 Set_Etype
(E1
, Universal_Integer
);
5840 -- Otherwise set type to Unsigned_64 to accomodate max values
5843 Set_Etype
(E1
, Standard_Unsigned_64
);
5847 Set_Is_Static_Expression
(N
, True);
5854 when Attribute_To_Any
=>
5856 Check_PolyORB_Attribute
;
5857 Set_Etype
(N
, RTE
(RE_Any
));
5863 when Attribute_Truncation
=>
5864 Check_Floating_Point_Type_1
;
5865 Resolve
(E1
, P_Base_Type
);
5866 Set_Etype
(N
, P_Base_Type
);
5872 when Attribute_Type_Class
=>
5875 Check_Not_Incomplete_Type
;
5876 Set_Etype
(N
, RTE
(RE_Type_Class
));
5882 when Attribute_TypeCode
=>
5884 Check_PolyORB_Attribute
;
5885 Set_Etype
(N
, RTE
(RE_TypeCode
));
5891 when Attribute_Type_Key
=>
5895 -- This processing belongs in Eval_Attribute ???
5898 function Type_Key
return String_Id
;
5899 -- A very preliminary implementation. For now, a signature
5900 -- consists of only the type name. This is clearly incomplete
5901 -- (e.g., adding a new field to a record type should change the
5902 -- type's Type_Key attribute).
5908 function Type_Key
return String_Id
is
5909 Full_Name
: constant String_Id
:=
5910 Fully_Qualified_Name_String
(Entity
(P
));
5913 -- Copy all characters in Full_Name but the trailing NUL
5916 for J
in 1 .. String_Length
(Full_Name
) - 1 loop
5917 Store_String_Char
(Get_String_Char
(Full_Name
, Int
(J
)));
5920 Store_String_Chars
("'Type_Key");
5925 Rewrite
(N
, Make_String_Literal
(Loc
, Type_Key
));
5928 Analyze_And_Resolve
(N
, Standard_String
);
5934 when Attribute_UET_Address
=>
5936 Check_Unit_Name
(P
);
5937 Set_Etype
(N
, RTE
(RE_Address
));
5939 -----------------------
5940 -- Unbiased_Rounding --
5941 -----------------------
5943 when Attribute_Unbiased_Rounding
=>
5944 Check_Floating_Point_Type_1
;
5945 Set_Etype
(N
, P_Base_Type
);
5946 Resolve
(E1
, P_Base_Type
);
5948 ----------------------
5949 -- Unchecked_Access --
5950 ----------------------
5952 when Attribute_Unchecked_Access
=>
5953 if Comes_From_Source
(N
) then
5954 Check_Restriction
(No_Unchecked_Access
, N
);
5957 Analyze_Access_Attribute
;
5959 -------------------------
5960 -- Unconstrained_Array --
5961 -------------------------
5963 when Attribute_Unconstrained_Array
=>
5966 Check_Not_Incomplete_Type
;
5967 Set_Etype
(N
, Standard_Boolean
);
5968 Set_Is_Static_Expression
(N
, True);
5970 ------------------------------
5971 -- Universal_Literal_String --
5972 ------------------------------
5974 -- This is a GNAT specific attribute whose prefix must be a named
5975 -- number where the expression is either a single numeric literal,
5976 -- or a numeric literal immediately preceded by a minus sign. The
5977 -- result is equivalent to a string literal containing the text of
5978 -- the literal as it appeared in the source program with a possible
5979 -- leading minus sign.
5981 when Attribute_Universal_Literal_String
=> Universal_Literal_String
:
5985 if not Is_Entity_Name
(P
)
5986 or else Ekind
(Entity
(P
)) not in Named_Kind
5988 Error_Attr_P
("prefix for % attribute must be named number");
5995 Src
: Source_Buffer_Ptr
;
5998 Expr
:= Original_Node
(Expression
(Parent
(Entity
(P
))));
6000 if Nkind
(Expr
) = N_Op_Minus
then
6002 Expr
:= Original_Node
(Right_Opnd
(Expr
));
6007 if not Nkind_In
(Expr
, N_Integer_Literal
, N_Real_Literal
) then
6009 ("named number for % attribute must be simple literal", N
);
6012 -- Build string literal corresponding to source literal text
6017 Store_String_Char
(Get_Char_Code
('-'));
6021 Src
:= Source_Text
(Get_Source_File_Index
(S
));
6023 while Src
(S
) /= ';' and then Src
(S
) /= ' ' loop
6024 Store_String_Char
(Get_Char_Code
(Src
(S
)));
6028 -- Now we rewrite the attribute with the string literal
6031 Make_String_Literal
(Loc
, End_String
));
6033 Set_Is_Static_Expression
(N
, True);
6036 end Universal_Literal_String
;
6038 -------------------------
6039 -- Unrestricted_Access --
6040 -------------------------
6042 -- This is a GNAT specific attribute which is like Access except that
6043 -- all scope checks and checks for aliased views are omitted. It is
6044 -- documented as being equivalent to the use of the Address attribute
6045 -- followed by an unchecked conversion to the target access type.
6047 when Attribute_Unrestricted_Access
=>
6049 -- If from source, deal with relevant restrictions
6051 if Comes_From_Source
(N
) then
6052 Check_Restriction
(No_Unchecked_Access
, N
);
6054 if Nkind
(P
) in N_Has_Entity
6055 and then Present
(Entity
(P
))
6056 and then Is_Object
(Entity
(P
))
6058 Check_Restriction
(No_Implicit_Aliasing
, N
);
6062 if Is_Entity_Name
(P
) then
6063 Set_Address_Taken
(Entity
(P
));
6066 -- It might seem reasonable to call Address_Checks here to apply the
6067 -- same set of semantic checks that we enforce for 'Address (after
6068 -- all we document Unrestricted_Access as being equivalent to the
6069 -- use of Address followed by an Unchecked_Conversion). However, if
6070 -- we do enable these checks, we get multiple failures in both the
6071 -- compiler run-time and in our regression test suite, so we leave
6072 -- out these checks for now. To be investigated further some time???
6076 -- Now complete analysis using common access processing
6078 Analyze_Access_Attribute
;
6084 when Attribute_Update
=> Update
: declare
6085 Common_Typ
: Entity_Id
;
6086 -- The common type of a multiple component update for a record
6088 Comps
: Elist_Id
:= No_Elist
;
6089 -- A list used in the resolution of a record update. It contains the
6090 -- entities of all record components processed so far.
6092 procedure Analyze_Array_Component_Update
(Assoc
: Node_Id
);
6093 -- Analyze and resolve array_component_association Assoc against the
6094 -- index of array type P_Type.
6096 procedure Analyze_Record_Component_Update
(Comp
: Node_Id
);
6097 -- Analyze and resolve record_component_association Comp against
6098 -- record type P_Type.
6100 ------------------------------------
6101 -- Analyze_Array_Component_Update --
6102 ------------------------------------
6104 procedure Analyze_Array_Component_Update
(Assoc
: Node_Id
) is
6108 Index_Typ
: Entity_Id
;
6112 -- The current association contains a sequence of indexes denoting
6113 -- an element of a multidimensional array:
6115 -- (Index_1, ..., Index_N)
6117 -- Examine each individual index and resolve it against the proper
6118 -- index type of the array.
6120 if Nkind
(First
(Choices
(Assoc
))) = N_Aggregate
then
6121 Expr
:= First
(Choices
(Assoc
));
6122 while Present
(Expr
) loop
6124 -- The use of others is illegal (SPARK RM 4.4.1(12))
6126 if Nkind
(Expr
) = N_Others_Choice
then
6128 ("others choice not allowed in attribute %", Expr
);
6130 -- Otherwise analyze and resolve all indexes
6133 Index
:= First
(Expressions
(Expr
));
6134 Index_Typ
:= First_Index
(P_Type
);
6135 while Present
(Index
) and then Present
(Index_Typ
) loop
6136 Analyze_And_Resolve
(Index
, Etype
(Index_Typ
));
6138 Next_Index
(Index_Typ
);
6141 -- Detect a case where the association either lacks an
6142 -- index or contains an extra index.
6144 if Present
(Index
) or else Present
(Index_Typ
) then
6146 ("dimension mismatch in index list", Assoc
);
6153 -- The current association denotes either a single component or a
6154 -- range of components of a one dimensional array:
6158 -- Resolve the index or its high and low bounds (if range) against
6159 -- the proper index type of the array.
6162 Index
:= First
(Choices
(Assoc
));
6163 Index_Typ
:= First_Index
(P_Type
);
6165 if Present
(Next_Index
(Index_Typ
)) then
6166 Error_Msg_N
("too few subscripts in array reference", Assoc
);
6169 while Present
(Index
) loop
6171 -- The use of others is illegal (SPARK RM 4.4.1(12))
6173 if Nkind
(Index
) = N_Others_Choice
then
6175 ("others choice not allowed in attribute %", Index
);
6177 -- The index denotes a range of elements
6179 elsif Nkind
(Index
) = N_Range
then
6180 Low
:= Low_Bound
(Index
);
6181 High
:= High_Bound
(Index
);
6183 Analyze_And_Resolve
(Low
, Etype
(Index_Typ
));
6184 Analyze_And_Resolve
(High
, Etype
(Index_Typ
));
6186 -- Add a range check to ensure that the bounds of the
6187 -- range are within the index type when this cannot be
6188 -- determined statically.
6190 if not Is_OK_Static_Expression
(Low
) then
6191 Set_Do_Range_Check
(Low
);
6194 if not Is_OK_Static_Expression
(High
) then
6195 Set_Do_Range_Check
(High
);
6198 -- Otherwise the index denotes a single element
6201 Analyze_And_Resolve
(Index
, Etype
(Index_Typ
));
6203 -- Add a range check to ensure that the index is within
6204 -- the index type when it is not possible to determine
6207 if not Is_OK_Static_Expression
(Index
) then
6208 Set_Do_Range_Check
(Index
);
6215 end Analyze_Array_Component_Update
;
6217 -------------------------------------
6218 -- Analyze_Record_Component_Update --
6219 -------------------------------------
6221 procedure Analyze_Record_Component_Update
(Comp
: Node_Id
) is
6222 Comp_Name
: constant Name_Id
:= Chars
(Comp
);
6223 Base_Typ
: Entity_Id
;
6224 Comp_Or_Discr
: Entity_Id
;
6227 -- Find the discriminant or component whose name corresponds to
6228 -- Comp. A simple character comparison is sufficient because all
6229 -- visible names within a record type are unique.
6231 Comp_Or_Discr
:= First_Entity
(P_Type
);
6232 while Present
(Comp_Or_Discr
) loop
6233 if Chars
(Comp_Or_Discr
) = Comp_Name
then
6235 -- Decorate the component reference by setting its entity
6236 -- and type for resolution purposes.
6238 Set_Entity
(Comp
, Comp_Or_Discr
);
6239 Set_Etype
(Comp
, Etype
(Comp_Or_Discr
));
6243 Comp_Or_Discr
:= Next_Entity
(Comp_Or_Discr
);
6246 -- Diagnose an illegal reference
6248 if Present
(Comp_Or_Discr
) then
6249 if Ekind
(Comp_Or_Discr
) = E_Discriminant
then
6251 ("attribute % may not modify record discriminants", Comp
);
6253 else pragma Assert
(Ekind
(Comp_Or_Discr
) = E_Component
);
6254 if Contains
(Comps
, Comp_Or_Discr
) then
6255 Error_Msg_N
("component & already updated", Comp
);
6257 -- Mark this component as processed
6260 Append_New_Elmt
(Comp_Or_Discr
, Comps
);
6264 -- The update aggregate mentions an entity that does not belong to
6268 Error_Msg_N
("& is not a component of aggregate subtype", Comp
);
6271 -- Verify the consistency of types when the current component is
6272 -- part of a miltiple component update.
6274 -- Comp_1, ..., Comp_N => <value>
6276 if Present
(Etype
(Comp
)) then
6277 Base_Typ
:= Base_Type
(Etype
(Comp
));
6279 -- Save the type of the first component reference as the
6280 -- remaning references (if any) must resolve to this type.
6282 if No
(Common_Typ
) then
6283 Common_Typ
:= Base_Typ
;
6285 elsif Base_Typ
/= Common_Typ
then
6287 ("components in choice list must have same type", Comp
);
6290 end Analyze_Record_Component_Update
;
6297 -- Start of processing for Update
6302 if not Is_Object_Reference
(P
) then
6303 Error_Attr_P
("prefix of attribute % must denote an object");
6305 elsif not Is_Array_Type
(P_Type
)
6306 and then not Is_Record_Type
(P_Type
)
6308 Error_Attr_P
("prefix of attribute % must be a record or array");
6310 elsif Is_Limited_View
(P_Type
) then
6311 Error_Attr
("prefix of attribute % cannot be limited", N
);
6313 elsif Nkind
(E1
) /= N_Aggregate
then
6314 Error_Attr
("attribute % requires component association list", N
);
6317 -- Inspect the update aggregate, looking at all the associations and
6318 -- choices. Perform the following checks:
6320 -- 1) Legality of "others" in all cases
6321 -- 2) Legality of <>
6322 -- 3) Component legality for arrays
6323 -- 4) Component legality for records
6325 -- The remaining checks are performed on the expanded attribute
6327 Assoc
:= First
(Component_Associations
(E1
));
6328 while Present
(Assoc
) loop
6330 -- The use of <> is illegal (SPARK RM 4.4.1(1))
6332 if Box_Present
(Assoc
) then
6334 ("default initialization not allowed in attribute %", Assoc
);
6336 -- Otherwise process the association
6339 Analyze
(Expression
(Assoc
));
6341 if Is_Array_Type
(P_Type
) then
6342 Analyze_Array_Component_Update
(Assoc
);
6344 elsif Is_Record_Type
(P_Type
) then
6346 -- Reset the common type used in a multiple component update
6347 -- as we are processing the contents of a new association.
6349 Common_Typ
:= Empty
;
6351 Comp
:= First
(Choices
(Assoc
));
6352 while Present
(Comp
) loop
6353 if Nkind
(Comp
) = N_Identifier
then
6354 Analyze_Record_Component_Update
(Comp
);
6356 -- The use of others is illegal (SPARK RM 4.4.1(5))
6358 elsif Nkind
(Comp
) = N_Others_Choice
then
6360 ("others choice not allowed in attribute %", Comp
);
6362 -- The name of a record component cannot appear in any
6367 ("name should be identifier or OTHERS", Comp
);
6378 -- The type of attribute 'Update is that of the prefix
6380 Set_Etype
(N
, P_Type
);
6387 when Attribute_Val
=> Val
: declare
6390 Check_Discrete_Type
;
6392 if Is_Boolean_Type
(P_Type
) then
6393 Error_Msg_Name_1
:= Aname
;
6394 Error_Msg_Name_2
:= Chars
(P_Type
);
6395 Check_SPARK_Restriction
6396 ("attribute% is not allowed for type%", P
);
6399 Resolve
(E1
, Any_Integer
);
6400 Set_Etype
(N
, P_Base_Type
);
6402 -- Note, we need a range check in general, but we wait for the
6403 -- Resolve call to do this, since we want to let Eval_Attribute
6404 -- have a chance to find an static illegality first.
6411 when Attribute_Valid
=>
6414 -- Ignore check for object if we have a 'Valid reference generated
6415 -- by the expanded code, since in some cases valid checks can occur
6416 -- on items that are names, but are not objects (e.g. attributes).
6418 if Comes_From_Source
(N
) then
6419 Check_Object_Reference
(P
);
6422 if not Is_Scalar_Type
(P_Type
) then
6423 Error_Attr_P
("object for % attribute must be of scalar type");
6426 -- If the attribute appears within the subtype's own predicate
6427 -- function, then issue a warning that this will cause infinite
6431 Pred_Func
: constant Entity_Id
:= Predicate_Function
(P_Type
);
6434 if Present
(Pred_Func
) and then Current_Scope
= Pred_Func
then
6436 ("attribute Valid requires a predicate check??", N
);
6437 Error_Msg_N
("\and will result in infinite recursion??", N
);
6441 Set_Etype
(N
, Standard_Boolean
);
6447 when Attribute_Valid_Scalars
=>
6449 Check_Object_Reference
(P
);
6450 Set_Etype
(N
, Standard_Boolean
);
6452 -- Following checks are only for source types
6454 if Comes_From_Source
(N
) then
6455 if not Scalar_Part_Present
(P_Type
) then
6457 ("??attribute % always True, no scalars to check");
6460 -- Not allowed for unchecked union type
6462 if Has_Unchecked_Union
(P_Type
) then
6464 ("attribute % not allowed for Unchecked_Union type");
6472 when Attribute_Value
=> Value
:
6474 Check_SPARK_Restriction_On_Attribute
;
6478 -- Case of enumeration type
6480 -- When an enumeration type appears in an attribute reference, all
6481 -- literals of the type are marked as referenced. This must only be
6482 -- done if the attribute reference appears in the current source.
6483 -- Otherwise the information on references may differ between a
6484 -- normal compilation and one that performs inlining.
6486 if Is_Enumeration_Type
(P_Type
)
6487 and then In_Extended_Main_Code_Unit
(N
)
6489 Check_Restriction
(No_Enumeration_Maps
, N
);
6491 -- Mark all enumeration literals as referenced, since the use of
6492 -- the Value attribute can implicitly reference any of the
6493 -- literals of the enumeration base type.
6496 Ent
: Entity_Id
:= First_Literal
(P_Base_Type
);
6498 while Present
(Ent
) loop
6499 Set_Referenced
(Ent
);
6505 -- Set Etype before resolving expression because expansion of
6506 -- expression may require enclosing type. Note that the type
6507 -- returned by 'Value is the base type of the prefix type.
6509 Set_Etype
(N
, P_Base_Type
);
6510 Validate_Non_Static_Attribute_Function_Call
;
6512 -- Check restriction No_Fixed_IO
6514 if Restriction_Check_Required
(No_Fixed_IO
)
6515 and then Is_Fixed_Point_Type
(P_Type
)
6517 Check_Restriction
(No_Fixed_IO
, P
);
6525 when Attribute_Value_Size
=>
6528 Check_Not_Incomplete_Type
;
6529 Set_Etype
(N
, Universal_Integer
);
6535 when Attribute_Version
=>
6538 Set_Etype
(N
, RTE
(RE_Version_String
));
6544 when Attribute_Wchar_T_Size
=>
6545 Standard_Attribute
(Interfaces_Wchar_T_Size
);
6551 when Attribute_Wide_Image
=> Wide_Image
:
6553 Check_SPARK_Restriction_On_Attribute
;
6555 Set_Etype
(N
, Standard_Wide_String
);
6557 Resolve
(E1
, P_Base_Type
);
6558 Validate_Non_Static_Attribute_Function_Call
;
6560 -- Check restriction No_Fixed_IO
6562 if Restriction_Check_Required
(No_Fixed_IO
)
6563 and then Is_Fixed_Point_Type
(P_Type
)
6565 Check_Restriction
(No_Fixed_IO
, P
);
6569 ---------------------
6570 -- Wide_Wide_Image --
6571 ---------------------
6573 when Attribute_Wide_Wide_Image
=> Wide_Wide_Image
:
6576 Set_Etype
(N
, Standard_Wide_Wide_String
);
6578 Resolve
(E1
, P_Base_Type
);
6579 Validate_Non_Static_Attribute_Function_Call
;
6581 -- Check restriction No_Fixed_IO
6583 if Restriction_Check_Required
(No_Fixed_IO
)
6584 and then Is_Fixed_Point_Type
(P_Type
)
6586 Check_Restriction
(No_Fixed_IO
, P
);
6588 end Wide_Wide_Image
;
6594 when Attribute_Wide_Value
=> Wide_Value
:
6596 Check_SPARK_Restriction_On_Attribute
;
6600 -- Set Etype before resolving expression because expansion
6601 -- of expression may require enclosing type.
6603 Set_Etype
(N
, P_Type
);
6604 Validate_Non_Static_Attribute_Function_Call
;
6606 -- Check restriction No_Fixed_IO
6608 if Restriction_Check_Required
(No_Fixed_IO
)
6609 and then Is_Fixed_Point_Type
(P_Type
)
6611 Check_Restriction
(No_Fixed_IO
, P
);
6615 ---------------------
6616 -- Wide_Wide_Value --
6617 ---------------------
6619 when Attribute_Wide_Wide_Value
=> Wide_Wide_Value
:
6624 -- Set Etype before resolving expression because expansion
6625 -- of expression may require enclosing type.
6627 Set_Etype
(N
, P_Type
);
6628 Validate_Non_Static_Attribute_Function_Call
;
6630 -- Check restriction No_Fixed_IO
6632 if Restriction_Check_Required
(No_Fixed_IO
)
6633 and then Is_Fixed_Point_Type
(P_Type
)
6635 Check_Restriction
(No_Fixed_IO
, P
);
6637 end Wide_Wide_Value
;
6639 ---------------------
6640 -- Wide_Wide_Width --
6641 ---------------------
6643 when Attribute_Wide_Wide_Width
=>
6646 Set_Etype
(N
, Universal_Integer
);
6652 when Attribute_Wide_Width
=>
6653 Check_SPARK_Restriction_On_Attribute
;
6656 Set_Etype
(N
, Universal_Integer
);
6662 when Attribute_Width
=>
6663 Check_SPARK_Restriction_On_Attribute
;
6666 Set_Etype
(N
, Universal_Integer
);
6672 when Attribute_Word_Size
=>
6673 Standard_Attribute
(System_Word_Size
);
6679 when Attribute_Write
=>
6681 Check_Stream_Attribute
(TSS_Stream_Write
);
6682 Set_Etype
(N
, Standard_Void_Type
);
6683 Resolve
(N
, Standard_Void_Type
);
6687 -- All errors raise Bad_Attribute, so that we get out before any further
6688 -- damage occurs when an error is detected (for example, if we check for
6689 -- one attribute expression, and the check succeeds, we want to be able
6690 -- to proceed securely assuming that an expression is in fact present.
6692 -- Note: we set the attribute analyzed in this case to prevent any
6693 -- attempt at reanalysis which could generate spurious error msgs.
6696 when Bad_Attribute
=>
6698 Set_Etype
(N
, Any_Type
);
6700 end Analyze_Attribute
;
6702 --------------------
6703 -- Eval_Attribute --
6704 --------------------
6706 procedure Eval_Attribute
(N
: Node_Id
) is
6707 Loc
: constant Source_Ptr
:= Sloc
(N
);
6708 Aname
: constant Name_Id
:= Attribute_Name
(N
);
6709 Id
: constant Attribute_Id
:= Get_Attribute_Id
(Aname
);
6710 P
: constant Node_Id
:= Prefix
(N
);
6712 C_Type
: constant Entity_Id
:= Etype
(N
);
6713 -- The type imposed by the context
6716 -- First expression, or Empty if none
6719 -- Second expression, or Empty if none
6721 P_Entity
: Entity_Id
;
6722 -- Entity denoted by prefix
6725 -- The type of the prefix
6727 P_Base_Type
: Entity_Id
;
6728 -- The base type of the prefix type
6730 P_Root_Type
: Entity_Id
;
6731 -- The root type of the prefix type
6734 -- True if the result is Static. This is set by the general processing
6735 -- to true if the prefix is static, and all expressions are static. It
6736 -- can be reset as processing continues for particular attributes. This
6737 -- flag can still be True if the reference raises a constraint error.
6738 -- Is_Static_Expression (N) is set to follow this value as it is set
6739 -- and we could always reference this, but it is convenient to have a
6740 -- simple short name to use, since it is frequently referenced.
6742 Lo_Bound
, Hi_Bound
: Node_Id
;
6743 -- Expressions for low and high bounds of type or array index referenced
6744 -- by First, Last, or Length attribute for array, set by Set_Bounds.
6747 -- Constraint error node used if we have an attribute reference has
6748 -- an argument that raises a constraint error. In this case we replace
6749 -- the attribute with a raise constraint_error node. This is important
6750 -- processing, since otherwise gigi might see an attribute which it is
6751 -- unprepared to deal with.
6753 procedure Check_Concurrent_Discriminant
(Bound
: Node_Id
);
6754 -- If Bound is a reference to a discriminant of a task or protected type
6755 -- occurring within the object's body, rewrite attribute reference into
6756 -- a reference to the corresponding discriminal. Use for the expansion
6757 -- of checks against bounds of entry family index subtypes.
6759 procedure Check_Expressions
;
6760 -- In case where the attribute is not foldable, the expressions, if
6761 -- any, of the attribute, are in a non-static context. This procedure
6762 -- performs the required additional checks.
6764 function Compile_Time_Known_Bounds
(Typ
: Entity_Id
) return Boolean;
6765 -- Determines if the given type has compile time known bounds. Note
6766 -- that we enter the case statement even in cases where the prefix
6767 -- type does NOT have known bounds, so it is important to guard any
6768 -- attempt to evaluate both bounds with a call to this function.
6770 procedure Compile_Time_Known_Attribute
(N
: Node_Id
; Val
: Uint
);
6771 -- This procedure is called when the attribute N has a non-static
6772 -- but compile time known value given by Val. It includes the
6773 -- necessary checks for out of range values.
6775 function Fore_Value
return Nat
;
6776 -- Computes the Fore value for the current attribute prefix, which is
6777 -- known to be a static fixed-point type. Used by Fore and Width.
6779 function Mantissa
return Uint
;
6780 -- Returns the Mantissa value for the prefix type
6782 procedure Set_Bounds
;
6783 -- Used for First, Last and Length attributes applied to an array or
6784 -- array subtype. Sets the variables Lo_Bound and Hi_Bound to the low
6785 -- and high bound expressions for the index referenced by the attribute
6786 -- designator (i.e. the first index if no expression is present, and the
6787 -- N'th index if the value N is present as an expression). Also used for
6788 -- First and Last of scalar types and for First_Valid and Last_Valid.
6789 -- Static is reset to False if the type or index type is not statically
6792 function Statically_Denotes_Entity
(N
: Node_Id
) return Boolean;
6793 -- Verify that the prefix of a potentially static array attribute
6794 -- satisfies the conditions of 4.9 (14).
6796 -----------------------------------
6797 -- Check_Concurrent_Discriminant --
6798 -----------------------------------
6800 procedure Check_Concurrent_Discriminant
(Bound
: Node_Id
) is
6802 -- The concurrent (task or protected) type
6805 if Nkind
(Bound
) = N_Identifier
6806 and then Ekind
(Entity
(Bound
)) = E_Discriminant
6807 and then Is_Concurrent_Record_Type
(Scope
(Entity
(Bound
)))
6809 Tsk
:= Corresponding_Concurrent_Type
(Scope
(Entity
(Bound
)));
6811 if In_Open_Scopes
(Tsk
) and then Has_Completion
(Tsk
) then
6813 -- Find discriminant of original concurrent type, and use
6814 -- its current discriminal, which is the renaming within
6815 -- the task/protected body.
6819 (Find_Body_Discriminal
(Entity
(Bound
)), Loc
));
6822 end Check_Concurrent_Discriminant
;
6824 -----------------------
6825 -- Check_Expressions --
6826 -----------------------
6828 procedure Check_Expressions
is
6832 while Present
(E
) loop
6833 Check_Non_Static_Context
(E
);
6836 end Check_Expressions
;
6838 ----------------------------------
6839 -- Compile_Time_Known_Attribute --
6840 ----------------------------------
6842 procedure Compile_Time_Known_Attribute
(N
: Node_Id
; Val
: Uint
) is
6843 T
: constant Entity_Id
:= Etype
(N
);
6846 Fold_Uint
(N
, Val
, False);
6848 -- Check that result is in bounds of the type if it is static
6850 if Is_In_Range
(N
, T
, Assume_Valid
=> False) then
6853 elsif Is_Out_Of_Range
(N
, T
) then
6854 Apply_Compile_Time_Constraint_Error
6855 (N
, "value not in range of}??", CE_Range_Check_Failed
);
6857 elsif not Range_Checks_Suppressed
(T
) then
6858 Enable_Range_Check
(N
);
6861 Set_Do_Range_Check
(N
, False);
6863 end Compile_Time_Known_Attribute
;
6865 -------------------------------
6866 -- Compile_Time_Known_Bounds --
6867 -------------------------------
6869 function Compile_Time_Known_Bounds
(Typ
: Entity_Id
) return Boolean is
6872 Compile_Time_Known_Value
(Type_Low_Bound
(Typ
))
6874 Compile_Time_Known_Value
(Type_High_Bound
(Typ
));
6875 end Compile_Time_Known_Bounds
;
6881 -- Note that the Fore calculation is based on the actual values
6882 -- of the bounds, and does not take into account possible rounding.
6884 function Fore_Value
return Nat
is
6885 Lo
: constant Uint
:= Expr_Value
(Type_Low_Bound
(P_Type
));
6886 Hi
: constant Uint
:= Expr_Value
(Type_High_Bound
(P_Type
));
6887 Small
: constant Ureal
:= Small_Value
(P_Type
);
6888 Lo_Real
: constant Ureal
:= Lo
* Small
;
6889 Hi_Real
: constant Ureal
:= Hi
* Small
;
6894 -- Bounds are given in terms of small units, so first compute
6895 -- proper values as reals.
6897 T
:= UR_Max
(abs Lo_Real
, abs Hi_Real
);
6900 -- Loop to compute proper value if more than one digit required
6902 while T
>= Ureal_10
loop
6914 -- Table of mantissa values accessed by function Computed using
6917 -- T'Mantissa = integer next above (D * log(10)/log(2)) + 1)
6919 -- where D is T'Digits (RM83 3.5.7)
6921 Mantissa_Value
: constant array (Nat
range 1 .. 40) of Nat
:= (
6963 function Mantissa
return Uint
is
6966 UI_From_Int
(Mantissa_Value
(UI_To_Int
(Digits_Value
(P_Type
))));
6973 procedure Set_Bounds
is
6979 -- For a string literal subtype, we have to construct the bounds.
6980 -- Valid Ada code never applies attributes to string literals, but
6981 -- it is convenient to allow the expander to generate attribute
6982 -- references of this type (e.g. First and Last applied to a string
6985 -- Note that the whole point of the E_String_Literal_Subtype is to
6986 -- avoid this construction of bounds, but the cases in which we
6987 -- have to materialize them are rare enough that we don't worry.
6989 -- The low bound is simply the low bound of the base type. The
6990 -- high bound is computed from the length of the string and this
6993 if Ekind
(P_Type
) = E_String_Literal_Subtype
then
6994 Ityp
:= Etype
(First_Index
(Base_Type
(P_Type
)));
6995 Lo_Bound
:= Type_Low_Bound
(Ityp
);
6998 Make_Integer_Literal
(Sloc
(P
),
7000 Expr_Value
(Lo_Bound
) + String_Literal_Length
(P_Type
) - 1);
7002 Set_Parent
(Hi_Bound
, P
);
7003 Analyze_And_Resolve
(Hi_Bound
, Etype
(Lo_Bound
));
7006 -- For non-array case, just get bounds of scalar type
7008 elsif Is_Scalar_Type
(P_Type
) then
7011 -- For a fixed-point type, we must freeze to get the attributes
7012 -- of the fixed-point type set now so we can reference them.
7014 if Is_Fixed_Point_Type
(P_Type
)
7015 and then not Is_Frozen
(Base_Type
(P_Type
))
7016 and then Compile_Time_Known_Value
(Type_Low_Bound
(P_Type
))
7017 and then Compile_Time_Known_Value
(Type_High_Bound
(P_Type
))
7019 Freeze_Fixed_Point_Type
(Base_Type
(P_Type
));
7022 -- For array case, get type of proper index
7028 Ndim
:= UI_To_Int
(Expr_Value
(E1
));
7031 Indx
:= First_Index
(P_Type
);
7032 for J
in 1 .. Ndim
- 1 loop
7036 -- If no index type, get out (some other error occurred, and
7037 -- we don't have enough information to complete the job).
7045 Ityp
:= Etype
(Indx
);
7048 -- A discrete range in an index constraint is allowed to be a
7049 -- subtype indication. This is syntactically a pain, but should
7050 -- not propagate to the entity for the corresponding index subtype.
7051 -- After checking that the subtype indication is legal, the range
7052 -- of the subtype indication should be transfered to the entity.
7053 -- The attributes for the bounds should remain the simple retrievals
7054 -- that they are now.
7056 Lo_Bound
:= Type_Low_Bound
(Ityp
);
7057 Hi_Bound
:= Type_High_Bound
(Ityp
);
7059 -- If subtype is non-static, result is definitely non-static
7061 if not Is_Static_Subtype
(Ityp
) then
7063 Set_Is_Static_Expression
(N
, False);
7065 -- Subtype is static, does it raise CE?
7067 elsif not Is_OK_Static_Subtype
(Ityp
) then
7068 Set_Raises_Constraint_Error
(N
);
7072 -------------------------------
7073 -- Statically_Denotes_Entity --
7074 -------------------------------
7076 function Statically_Denotes_Entity
(N
: Node_Id
) return Boolean is
7080 if not Is_Entity_Name
(N
) then
7087 Nkind
(Parent
(E
)) /= N_Object_Renaming_Declaration
7088 or else Statically_Denotes_Entity
(Renamed_Object
(E
));
7089 end Statically_Denotes_Entity
;
7091 -- Start of processing for Eval_Attribute
7094 -- Initialize result as non-static, will be reset if appropriate
7096 Set_Is_Static_Expression
(N
, False);
7099 -- Acquire first two expressions (at the moment, no attributes take more
7100 -- than two expressions in any case).
7102 if Present
(Expressions
(N
)) then
7103 E1
:= First
(Expressions
(N
));
7110 -- Special processing for Enabled attribute. This attribute has a very
7111 -- special prefix, and the easiest way to avoid lots of special checks
7112 -- to protect this special prefix from causing trouble is to deal with
7113 -- this attribute immediately and be done with it.
7115 if Id
= Attribute_Enabled
then
7117 -- We skip evaluation if the expander is not active. This is not just
7118 -- an optimization. It is of key importance that we not rewrite the
7119 -- attribute in a generic template, since we want to pick up the
7120 -- setting of the check in the instance, and testing expander active
7121 -- is as easy way of doing this as any.
7123 if Expander_Active
then
7125 C
: constant Check_Id
:= Get_Check_Id
(Chars
(P
));
7130 if C
in Predefined_Check_Id
then
7131 R
:= Scope_Suppress
.Suppress
(C
);
7133 R
:= Is_Check_Suppressed
(Empty
, C
);
7137 R
:= Is_Check_Suppressed
(Entity
(E1
), C
);
7140 Rewrite
(N
, New_Occurrence_Of
(Boolean_Literals
(not R
), Loc
));
7147 -- Special processing for cases where the prefix is an object. For
7148 -- this purpose, a string literal counts as an object (attributes
7149 -- of string literals can only appear in generated code).
7151 if Is_Object_Reference
(P
) or else Nkind
(P
) = N_String_Literal
then
7153 -- For Component_Size, the prefix is an array object, and we apply
7154 -- the attribute to the type of the object. This is allowed for
7155 -- both unconstrained and constrained arrays, since the bounds
7156 -- have no influence on the value of this attribute.
7158 if Id
= Attribute_Component_Size
then
7159 P_Entity
:= Etype
(P
);
7161 -- For First and Last, the prefix is an array object, and we apply
7162 -- the attribute to the type of the array, but we need a constrained
7163 -- type for this, so we use the actual subtype if available.
7165 elsif Id
= Attribute_First
or else
7166 Id
= Attribute_Last
or else
7167 Id
= Attribute_Length
7170 AS
: constant Entity_Id
:= Get_Actual_Subtype_If_Available
(P
);
7173 if Present
(AS
) and then Is_Constrained
(AS
) then
7176 -- If we have an unconstrained type we cannot fold
7184 -- For Size, give size of object if available, otherwise we
7185 -- cannot fold Size.
7187 elsif Id
= Attribute_Size
then
7188 if Is_Entity_Name
(P
)
7189 and then Known_Esize
(Entity
(P
))
7191 Compile_Time_Known_Attribute
(N
, Esize
(Entity
(P
)));
7199 -- For Alignment, give size of object if available, otherwise we
7200 -- cannot fold Alignment.
7202 elsif Id
= Attribute_Alignment
then
7203 if Is_Entity_Name
(P
)
7204 and then Known_Alignment
(Entity
(P
))
7206 Fold_Uint
(N
, Alignment
(Entity
(P
)), Static
);
7214 -- For Lock_Free, we apply the attribute to the type of the object.
7215 -- This is allowed since we have already verified that the type is a
7218 elsif Id
= Attribute_Lock_Free
then
7219 P_Entity
:= Etype
(P
);
7221 -- No other attributes for objects are folded
7228 -- Cases where P is not an object. Cannot do anything if P is not the
7229 -- name of an entity.
7231 elsif not Is_Entity_Name
(P
) then
7235 -- Otherwise get prefix entity
7238 P_Entity
:= Entity
(P
);
7241 -- If we are asked to evaluate an attribute where the prefix is a
7242 -- non-frozen generic actual type whose RM_Size is still set to zero,
7243 -- then abandon the effort.
7245 if Is_Type
(P_Entity
)
7246 and then (not Is_Frozen
(P_Entity
)
7247 and then Is_Generic_Actual_Type
(P_Entity
)
7248 and then RM_Size
(P_Entity
) = 0)
7250 -- However, the attribute Unconstrained_Array must be evaluated,
7251 -- since it is documented to be a static attribute (and can for
7252 -- example appear in a Compile_Time_Warning pragma). The frozen
7253 -- status of the type does not affect its evaluation.
7255 and then Id
/= Attribute_Unconstrained_Array
7260 -- At this stage P_Entity is the entity to which the attribute
7261 -- is to be applied. This is usually simply the entity of the
7262 -- prefix, except in some cases of attributes for objects, where
7263 -- as described above, we apply the attribute to the object type.
7265 -- Here is where we make sure that static attributes are properly
7266 -- marked as such. These are attributes whose prefix is a static
7267 -- scalar subtype, whose result is scalar, and whose arguments, if
7268 -- present, are static scalar expressions. Note that such references
7269 -- are static expressions even if they raise Constraint_Error.
7271 -- For example, Boolean'Pos (1/0 = 0) is a static expression, even
7272 -- though evaluating it raises constraint error. This means that a
7273 -- declaration like:
7275 -- X : constant := (if True then 1 else Boolean'Pos (1/0 = 0));
7277 -- is legal, since here this expression appears in a statically
7278 -- unevaluated position, so it does not actually raise an exception.
7280 if Is_Scalar_Type
(P_Entity
)
7281 and then (not Is_Generic_Type
(P_Entity
))
7282 and then Is_Static_Subtype
(P_Entity
)
7283 and then Is_Scalar_Type
(Etype
(N
))
7286 or else (Is_Static_Expression
(E1
)
7287 and then Is_Scalar_Type
(Etype
(E1
))))
7290 or else (Is_Static_Expression
(E2
)
7291 and then Is_Scalar_Type
(Etype
(E1
))))
7294 Set_Is_Static_Expression
(N
, True);
7297 -- First foldable possibility is a scalar or array type (RM 4.9(7))
7298 -- that is not generic (generic types are eliminated by RM 4.9(25)).
7299 -- Note we allow non-static non-generic types at this stage as further
7302 if Is_Type
(P_Entity
)
7303 and then (Is_Scalar_Type
(P_Entity
) or Is_Array_Type
(P_Entity
))
7304 and then (not Is_Generic_Type
(P_Entity
))
7308 -- Second foldable possibility is an array object (RM 4.9(8))
7310 elsif (Ekind
(P_Entity
) = E_Variable
7312 Ekind
(P_Entity
) = E_Constant
)
7313 and then Is_Array_Type
(Etype
(P_Entity
))
7314 and then (not Is_Generic_Type
(Etype
(P_Entity
)))
7316 P_Type
:= Etype
(P_Entity
);
7318 -- If the entity is an array constant with an unconstrained nominal
7319 -- subtype then get the type from the initial value. If the value has
7320 -- been expanded into assignments, there is no expression and the
7321 -- attribute reference remains dynamic.
7323 -- We could do better here and retrieve the type ???
7325 if Ekind
(P_Entity
) = E_Constant
7326 and then not Is_Constrained
(P_Type
)
7328 if No
(Constant_Value
(P_Entity
)) then
7331 P_Type
:= Etype
(Constant_Value
(P_Entity
));
7335 -- Definite must be folded if the prefix is not a generic type, that
7336 -- is to say if we are within an instantiation. Same processing applies
7337 -- to the GNAT attributes Atomic_Always_Lock_Free, Has_Discriminants,
7338 -- Lock_Free, Type_Class, Has_Tagged_Value, and Unconstrained_Array.
7340 elsif (Id
= Attribute_Atomic_Always_Lock_Free
or else
7341 Id
= Attribute_Definite
or else
7342 Id
= Attribute_Has_Access_Values
or else
7343 Id
= Attribute_Has_Discriminants
or else
7344 Id
= Attribute_Has_Tagged_Values
or else
7345 Id
= Attribute_Lock_Free
or else
7346 Id
= Attribute_Type_Class
or else
7347 Id
= Attribute_Unconstrained_Array
or else
7348 Id
= Attribute_Max_Alignment_For_Allocation
)
7349 and then not Is_Generic_Type
(P_Entity
)
7353 -- We can fold 'Size applied to a type if the size is known (as happens
7354 -- for a size from an attribute definition clause). At this stage, this
7355 -- can happen only for types (e.g. record types) for which the size is
7356 -- always non-static. We exclude generic types from consideration (since
7357 -- they have bogus sizes set within templates).
7359 elsif Id
= Attribute_Size
7360 and then Is_Type
(P_Entity
)
7361 and then (not Is_Generic_Type
(P_Entity
))
7362 and then Known_Static_RM_Size
(P_Entity
)
7364 Compile_Time_Known_Attribute
(N
, RM_Size
(P_Entity
));
7367 -- We can fold 'Alignment applied to a type if the alignment is known
7368 -- (as happens for an alignment from an attribute definition clause).
7369 -- At this stage, this can happen only for types (e.g. record types) for
7370 -- which the size is always non-static. We exclude generic types from
7371 -- consideration (since they have bogus sizes set within templates).
7373 elsif Id
= Attribute_Alignment
7374 and then Is_Type
(P_Entity
)
7375 and then (not Is_Generic_Type
(P_Entity
))
7376 and then Known_Alignment
(P_Entity
)
7378 Compile_Time_Known_Attribute
(N
, Alignment
(P_Entity
));
7381 -- If this is an access attribute that is known to fail accessibility
7382 -- check, rewrite accordingly.
7384 elsif Attribute_Name
(N
) = Name_Access
7385 and then Raises_Constraint_Error
(N
)
7388 Make_Raise_Program_Error
(Loc
,
7389 Reason
=> PE_Accessibility_Check_Failed
));
7390 Set_Etype
(N
, C_Type
);
7393 -- No other cases are foldable (they certainly aren't static, and at
7394 -- the moment we don't try to fold any cases other than the ones above).
7401 -- If either attribute or the prefix is Any_Type, then propagate
7402 -- Any_Type to the result and don't do anything else at all.
7404 if P_Type
= Any_Type
7405 or else (Present
(E1
) and then Etype
(E1
) = Any_Type
)
7406 or else (Present
(E2
) and then Etype
(E2
) = Any_Type
)
7408 Set_Etype
(N
, Any_Type
);
7412 -- Scalar subtype case. We have not yet enforced the static requirement
7413 -- of (RM 4.9(7)) and we don't intend to just yet, since there are cases
7414 -- of non-static attribute references (e.g. S'Digits for a non-static
7415 -- floating-point type, which we can compute at compile time).
7417 -- Note: this folding of non-static attributes is not simply a case of
7418 -- optimization. For many of the attributes affected, Gigi cannot handle
7419 -- the attribute and depends on the front end having folded them away.
7421 -- Note: although we don't require staticness at this stage, we do set
7422 -- the Static variable to record the staticness, for easy reference by
7423 -- those attributes where it matters (e.g. Succ and Pred), and also to
7424 -- be used to ensure that non-static folded things are not marked as
7425 -- being static (a check that is done right at the end).
7427 P_Root_Type
:= Root_Type
(P_Type
);
7428 P_Base_Type
:= Base_Type
(P_Type
);
7430 -- If the root type or base type is generic, then we cannot fold. This
7431 -- test is needed because subtypes of generic types are not always
7432 -- marked as being generic themselves (which seems odd???)
7434 if Is_Generic_Type
(P_Root_Type
)
7435 or else Is_Generic_Type
(P_Base_Type
)
7440 if Is_Scalar_Type
(P_Type
) then
7441 if not Is_Static_Subtype
(P_Type
) then
7443 Set_Is_Static_Expression
(N
, False);
7444 elsif not Is_OK_Static_Subtype
(P_Type
) then
7445 Set_Raises_Constraint_Error
(N
);
7448 -- Array case. We enforce the constrained requirement of (RM 4.9(7-8))
7449 -- since we can't do anything with unconstrained arrays. In addition,
7450 -- only the First, Last and Length attributes are possibly static.
7452 -- Atomic_Always_Lock_Free, Definite, Has_Access_Values,
7453 -- Has_Discriminants, Has_Tagged_Values, Lock_Free, Type_Class, and
7454 -- Unconstrained_Array are again exceptions, because they apply as well
7455 -- to unconstrained types.
7457 -- In addition Component_Size is an exception since it is possibly
7458 -- foldable, even though it is never static, and it does apply to
7459 -- unconstrained arrays. Furthermore, it is essential to fold this
7460 -- in the packed case, since otherwise the value will be incorrect.
7462 elsif Id
= Attribute_Atomic_Always_Lock_Free
or else
7463 Id
= Attribute_Definite
or else
7464 Id
= Attribute_Has_Access_Values
or else
7465 Id
= Attribute_Has_Discriminants
or else
7466 Id
= Attribute_Has_Tagged_Values
or else
7467 Id
= Attribute_Lock_Free
or else
7468 Id
= Attribute_Type_Class
or else
7469 Id
= Attribute_Unconstrained_Array
or else
7470 Id
= Attribute_Component_Size
7473 Set_Is_Static_Expression
(N
, False);
7475 elsif Id
/= Attribute_Max_Alignment_For_Allocation
then
7476 if not Is_Constrained
(P_Type
)
7477 or else (Id
/= Attribute_First
and then
7478 Id
/= Attribute_Last
and then
7479 Id
/= Attribute_Length
)
7485 -- The rules in (RM 4.9(7,8)) require a static array, but as in the
7486 -- scalar case, we hold off on enforcing staticness, since there are
7487 -- cases which we can fold at compile time even though they are not
7488 -- static (e.g. 'Length applied to a static index, even though other
7489 -- non-static indexes make the array type non-static). This is only
7490 -- an optimization, but it falls out essentially free, so why not.
7491 -- Again we compute the variable Static for easy reference later
7492 -- (note that no array attributes are static in Ada 83).
7494 -- We also need to set Static properly for subsequent legality checks
7495 -- which might otherwise accept non-static constants in contexts
7496 -- where they are not legal.
7499 Ada_Version
>= Ada_95
and then Statically_Denotes_Entity
(P
);
7500 Set_Is_Static_Expression
(N
, Static
);
7506 Nod
:= First_Index
(P_Type
);
7508 -- The expression is static if the array type is constrained
7509 -- by given bounds, and not by an initial expression. Constant
7510 -- strings are static in any case.
7512 if Root_Type
(P_Type
) /= Standard_String
then
7514 Static
and then not Is_Constr_Subt_For_U_Nominal
(P_Type
);
7515 Set_Is_Static_Expression
(N
, Static
);
7519 while Present
(Nod
) loop
7520 if not Is_Static_Subtype
(Etype
(Nod
)) then
7522 Set_Is_Static_Expression
(N
, False);
7523 elsif not Is_OK_Static_Subtype
(Etype
(Nod
)) then
7524 Set_Raises_Constraint_Error
(N
);
7527 -- If however the index type is generic, or derived from
7528 -- one, attributes cannot be folded.
7530 if Is_Generic_Type
(Root_Type
(Etype
(Nod
)))
7531 and then Id
/= Attribute_Component_Size
7541 -- Check any expressions that are present. Note that these expressions,
7542 -- depending on the particular attribute type, are either part of the
7543 -- attribute designator, or they are arguments in a case where the
7544 -- attribute reference returns a function. In the latter case, the
7545 -- rule in (RM 4.9(22)) applies and in particular requires the type
7546 -- of the expressions to be scalar in order for the attribute to be
7547 -- considered to be static.
7554 while Present
(E
) loop
7556 -- If expression is not static, then the attribute reference
7557 -- result certainly cannot be static.
7559 if not Is_Static_Expression
(E
) then
7561 Set_Is_Static_Expression
(N
, False);
7564 if Raises_Constraint_Error
(E
) then
7565 Set_Raises_Constraint_Error
(N
);
7568 -- If the result is not known at compile time, or is not of
7569 -- a scalar type, then the result is definitely not static,
7570 -- so we can quit now.
7572 if not Compile_Time_Known_Value
(E
)
7573 or else not Is_Scalar_Type
(Etype
(E
))
7575 -- An odd special case, if this is a Pos attribute, this
7576 -- is where we need to apply a range check since it does
7577 -- not get done anywhere else.
7579 if Id
= Attribute_Pos
then
7580 if Is_Integer_Type
(Etype
(E
)) then
7581 Apply_Range_Check
(E
, Etype
(N
));
7588 -- If the expression raises a constraint error, then so does
7589 -- the attribute reference. We keep going in this case because
7590 -- we are still interested in whether the attribute reference
7591 -- is static even if it is not static.
7593 elsif Raises_Constraint_Error
(E
) then
7594 Set_Raises_Constraint_Error
(N
);
7600 if Raises_Constraint_Error
(Prefix
(N
)) then
7605 -- Deal with the case of a static attribute reference that raises
7606 -- constraint error. The Raises_Constraint_Error flag will already
7607 -- have been set, and the Static flag shows whether the attribute
7608 -- reference is static. In any case we certainly can't fold such an
7609 -- attribute reference.
7611 -- Note that the rewriting of the attribute node with the constraint
7612 -- error node is essential in this case, because otherwise Gigi might
7613 -- blow up on one of the attributes it never expects to see.
7615 -- The constraint_error node must have the type imposed by the context,
7616 -- to avoid spurious errors in the enclosing expression.
7618 if Raises_Constraint_Error
(N
) then
7620 Make_Raise_Constraint_Error
(Sloc
(N
),
7621 Reason
=> CE_Range_Check_Failed
);
7622 Set_Etype
(CE_Node
, Etype
(N
));
7623 Set_Raises_Constraint_Error
(CE_Node
);
7625 Rewrite
(N
, Relocate_Node
(CE_Node
));
7626 Set_Raises_Constraint_Error
(N
, True);
7630 -- At this point we have a potentially foldable attribute reference.
7631 -- If Static is set, then the attribute reference definitely obeys
7632 -- the requirements in (RM 4.9(7,8,22)), and it definitely can be
7633 -- folded. If Static is not set, then the attribute may or may not
7634 -- be foldable, and the individual attribute processing routines
7635 -- test Static as required in cases where it makes a difference.
7637 -- In the case where Static is not set, we do know that all the
7638 -- expressions present are at least known at compile time (we assumed
7639 -- above that if this was not the case, then there was no hope of static
7640 -- evaluation). However, we did not require that the bounds of the
7641 -- prefix type be compile time known, let alone static). That's because
7642 -- there are many attributes that can be computed at compile time on
7643 -- non-static subtypes, even though such references are not static
7646 -- For VAX float, the root type is an IEEE type. So make sure to use the
7647 -- base type instead of the root-type for floating point attributes.
7651 -- Attributes related to Ada 2012 iterators (placeholder ???)
7653 when Attribute_Constant_Indexing |
7654 Attribute_Default_Iterator |
7655 Attribute_Implicit_Dereference |
7656 Attribute_Iterator_Element |
7657 Attribute_Iterable |
7658 Attribute_Variable_Indexing
=> null;
7660 -- Internal attributes used to deal with Ada 2012 delayed aspects.
7661 -- These were already rejected by the parser. Thus they shouldn't
7664 when Internal_Attribute_Id
=>
7665 raise Program_Error
;
7671 when Attribute_Adjacent
=>
7675 (P_Base_Type
, Expr_Value_R
(E1
), Expr_Value_R
(E2
)),
7682 when Attribute_Aft
=>
7683 Fold_Uint
(N
, Aft_Value
(P_Type
), Static
);
7689 when Attribute_Alignment
=> Alignment_Block
: declare
7690 P_TypeA
: constant Entity_Id
:= Underlying_Type
(P_Type
);
7693 -- Fold if alignment is set and not otherwise
7695 if Known_Alignment
(P_TypeA
) then
7696 Fold_Uint
(N
, Alignment
(P_TypeA
), Static
);
7698 end Alignment_Block
;
7700 -----------------------------
7701 -- Atomic_Always_Lock_Free --
7702 -----------------------------
7704 -- Atomic_Always_Lock_Free attribute is a Boolean, thus no need to fold
7707 when Attribute_Atomic_Always_Lock_Free
=> Atomic_Always_Lock_Free
:
7709 V
: constant Entity_Id
:=
7711 (Support_Atomic_Primitives_On_Target
7712 and then Support_Atomic_Primitives
(P_Type
));
7715 Rewrite
(N
, New_Occurrence_Of
(V
, Loc
));
7717 -- Analyze and resolve as boolean. Note that this attribute is a
7718 -- static attribute in GNAT.
7720 Analyze_And_Resolve
(N
, Standard_Boolean
);
7722 Set_Is_Static_Expression
(N
, True);
7723 end Atomic_Always_Lock_Free
;
7729 -- Bit can never be folded
7731 when Attribute_Bit
=>
7738 -- Body_version can never be static
7740 when Attribute_Body_Version
=>
7747 when Attribute_Ceiling
=>
7749 (N
, Eval_Fat
.Ceiling
(P_Base_Type
, Expr_Value_R
(E1
)), Static
);
7751 --------------------
7752 -- Component_Size --
7753 --------------------
7755 when Attribute_Component_Size
=>
7756 if Known_Static_Component_Size
(P_Type
) then
7757 Fold_Uint
(N
, Component_Size
(P_Type
), Static
);
7764 when Attribute_Compose
=>
7767 Eval_Fat
.Compose
(P_Base_Type
, Expr_Value_R
(E1
), Expr_Value
(E2
)),
7774 -- Constrained is never folded for now, there may be cases that
7775 -- could be handled at compile time. To be looked at later.
7777 when Attribute_Constrained
=>
7784 when Attribute_Copy_Sign
=>
7788 (P_Base_Type
, Expr_Value_R
(E1
), Expr_Value_R
(E2
)),
7795 when Attribute_Definite
=>
7796 Rewrite
(N
, New_Occurrence_Of
(
7797 Boolean_Literals
(not Is_Indefinite_Subtype
(P_Entity
)), Loc
));
7798 Analyze_And_Resolve
(N
, Standard_Boolean
);
7804 when Attribute_Delta
=>
7805 Fold_Ureal
(N
, Delta_Value
(P_Type
), True);
7811 when Attribute_Denorm
=>
7813 (N
, UI_From_Int
(Boolean'Pos (Has_Denormals
(P_Type
))), Static
);
7815 ---------------------
7816 -- Descriptor_Size --
7817 ---------------------
7819 when Attribute_Descriptor_Size
=>
7826 when Attribute_Digits
=>
7827 Fold_Uint
(N
, Digits_Value
(P_Type
), Static
);
7833 when Attribute_Emax
=>
7835 -- Ada 83 attribute is defined as (RM83 3.5.8)
7837 -- T'Emax = 4 * T'Mantissa
7839 Fold_Uint
(N
, 4 * Mantissa
, Static
);
7845 when Attribute_Enum_Rep
=>
7847 -- For an enumeration type with a non-standard representation use
7848 -- the Enumeration_Rep field of the proper constant. Note that this
7849 -- will not work for types Character/Wide_[Wide-]Character, since no
7850 -- real entities are created for the enumeration literals, but that
7851 -- does not matter since these two types do not have non-standard
7852 -- representations anyway.
7854 if Is_Enumeration_Type
(P_Type
)
7855 and then Has_Non_Standard_Rep
(P_Type
)
7857 Fold_Uint
(N
, Enumeration_Rep
(Expr_Value_E
(E1
)), Static
);
7859 -- For enumeration types with standard representations and all
7860 -- other cases (i.e. all integer and modular types), Enum_Rep
7861 -- is equivalent to Pos.
7864 Fold_Uint
(N
, Expr_Value
(E1
), Static
);
7871 when Attribute_Enum_Val
=> Enum_Val
: declare
7875 -- We have something like Enum_Type'Enum_Val (23), so search for a
7876 -- corresponding value in the list of Enum_Rep values for the type.
7878 Lit
:= First_Literal
(P_Base_Type
);
7880 if Enumeration_Rep
(Lit
) = Expr_Value
(E1
) then
7881 Fold_Uint
(N
, Enumeration_Pos
(Lit
), Static
);
7888 Apply_Compile_Time_Constraint_Error
7889 (N
, "no representation value matches",
7890 CE_Range_Check_Failed
,
7891 Warn
=> not Static
);
7901 when Attribute_Epsilon
=>
7903 -- Ada 83 attribute is defined as (RM83 3.5.8)
7905 -- T'Epsilon = 2.0**(1 - T'Mantissa)
7907 Fold_Ureal
(N
, Ureal_2
** (1 - Mantissa
), True);
7913 when Attribute_Exponent
=>
7915 Eval_Fat
.Exponent
(P_Base_Type
, Expr_Value_R
(E1
)), Static
);
7921 when Attribute_First
=> First_Attr
:
7925 if Compile_Time_Known_Value
(Lo_Bound
) then
7926 if Is_Real_Type
(P_Type
) then
7927 Fold_Ureal
(N
, Expr_Value_R
(Lo_Bound
), Static
);
7929 Fold_Uint
(N
, Expr_Value
(Lo_Bound
), Static
);
7933 Check_Concurrent_Discriminant
(Lo_Bound
);
7941 when Attribute_First_Valid
=> First_Valid
:
7943 if Has_Predicates
(P_Type
)
7944 and then Has_Static_Predicate
(P_Type
)
7947 FirstN
: constant Node_Id
:=
7948 First
(Static_Discrete_Predicate
(P_Type
));
7950 if Nkind
(FirstN
) = N_Range
then
7951 Fold_Uint
(N
, Expr_Value
(Low_Bound
(FirstN
)), Static
);
7953 Fold_Uint
(N
, Expr_Value
(FirstN
), Static
);
7959 Fold_Uint
(N
, Expr_Value
(Lo_Bound
), Static
);
7967 when Attribute_Fixed_Value
=>
7974 when Attribute_Floor
=>
7976 (N
, Eval_Fat
.Floor
(P_Base_Type
, Expr_Value_R
(E1
)), Static
);
7982 when Attribute_Fore
=>
7983 if Compile_Time_Known_Bounds
(P_Type
) then
7984 Fold_Uint
(N
, UI_From_Int
(Fore_Value
), Static
);
7991 when Attribute_Fraction
=>
7993 (N
, Eval_Fat
.Fraction
(P_Base_Type
, Expr_Value_R
(E1
)), Static
);
7995 -----------------------
7996 -- Has_Access_Values --
7997 -----------------------
7999 when Attribute_Has_Access_Values
=>
8000 Rewrite
(N
, New_Occurrence_Of
8001 (Boolean_Literals
(Has_Access_Values
(P_Root_Type
)), Loc
));
8002 Analyze_And_Resolve
(N
, Standard_Boolean
);
8004 -----------------------
8005 -- Has_Discriminants --
8006 -----------------------
8008 when Attribute_Has_Discriminants
=>
8009 Rewrite
(N
, New_Occurrence_Of
(
8010 Boolean_Literals
(Has_Discriminants
(P_Entity
)), Loc
));
8011 Analyze_And_Resolve
(N
, Standard_Boolean
);
8013 ----------------------
8014 -- Has_Same_Storage --
8015 ----------------------
8017 when Attribute_Has_Same_Storage
=>
8020 -----------------------
8021 -- Has_Tagged_Values --
8022 -----------------------
8024 when Attribute_Has_Tagged_Values
=>
8025 Rewrite
(N
, New_Occurrence_Of
8026 (Boolean_Literals
(Has_Tagged_Component
(P_Root_Type
)), Loc
));
8027 Analyze_And_Resolve
(N
, Standard_Boolean
);
8033 when Attribute_Identity
=>
8040 -- Image is a scalar attribute, but is never static, because it is
8041 -- not a static function (having a non-scalar argument (RM 4.9(22))
8042 -- However, we can constant-fold the image of an enumeration literal
8043 -- if names are available.
8045 when Attribute_Image
=>
8046 if Is_Entity_Name
(E1
)
8047 and then Ekind
(Entity
(E1
)) = E_Enumeration_Literal
8048 and then not Discard_Names
(First_Subtype
(Etype
(E1
)))
8049 and then not Global_Discard_Names
8052 Lit
: constant Entity_Id
:= Entity
(E1
);
8056 Get_Unqualified_Decoded_Name_String
(Chars
(Lit
));
8057 Set_Casing
(All_Upper_Case
);
8058 Store_String_Chars
(Name_Buffer
(1 .. Name_Len
));
8060 Rewrite
(N
, Make_String_Literal
(Loc
, Strval
=> Str
));
8061 Analyze_And_Resolve
(N
, Standard_String
);
8062 Set_Is_Static_Expression
(N
, False);
8070 -- Img is a scalar attribute, but is never static, because it is
8071 -- not a static function (having a non-scalar argument (RM 4.9(22))
8073 when Attribute_Img
=>
8080 -- We never try to fold Integer_Value (though perhaps we could???)
8082 when Attribute_Integer_Value
=>
8089 -- Invalid_Value is a scalar attribute that is never static, because
8090 -- the value is by design out of range.
8092 when Attribute_Invalid_Value
=>
8099 when Attribute_Large
=>
8101 -- For fixed-point, we use the identity:
8103 -- T'Large = (2.0**T'Mantissa - 1.0) * T'Small
8105 if Is_Fixed_Point_Type
(P_Type
) then
8107 Make_Op_Multiply
(Loc
,
8109 Make_Op_Subtract
(Loc
,
8113 Make_Real_Literal
(Loc
, Ureal_2
),
8115 Make_Attribute_Reference
(Loc
,
8117 Attribute_Name
=> Name_Mantissa
)),
8118 Right_Opnd
=> Make_Real_Literal
(Loc
, Ureal_1
)),
8121 Make_Real_Literal
(Loc
, Small_Value
(Entity
(P
)))));
8123 Analyze_And_Resolve
(N
, C_Type
);
8125 -- Floating-point (Ada 83 compatibility)
8128 -- Ada 83 attribute is defined as (RM83 3.5.8)
8130 -- T'Large = 2.0**T'Emax * (1.0 - 2.0**(-T'Mantissa))
8134 -- T'Emax = 4 * T'Mantissa
8138 Ureal_2
** (4 * Mantissa
) * (Ureal_1
- Ureal_2
** (-Mantissa
)),
8146 when Attribute_Lock_Free
=> Lock_Free
: declare
8147 V
: constant Entity_Id
:= Boolean_Literals
(Uses_Lock_Free
(P_Type
));
8150 Rewrite
(N
, New_Occurrence_Of
(V
, Loc
));
8152 -- Analyze and resolve as boolean. Note that this attribute is a
8153 -- static attribute in GNAT.
8155 Analyze_And_Resolve
(N
, Standard_Boolean
);
8157 Set_Is_Static_Expression
(N
, True);
8164 when Attribute_Last
=> Last_Attr
:
8168 if Compile_Time_Known_Value
(Hi_Bound
) then
8169 if Is_Real_Type
(P_Type
) then
8170 Fold_Ureal
(N
, Expr_Value_R
(Hi_Bound
), Static
);
8172 Fold_Uint
(N
, Expr_Value
(Hi_Bound
), Static
);
8176 Check_Concurrent_Discriminant
(Hi_Bound
);
8184 when Attribute_Last_Valid
=> Last_Valid
:
8186 if Has_Predicates
(P_Type
)
8187 and then Has_Static_Predicate
(P_Type
)
8190 LastN
: constant Node_Id
:=
8191 Last
(Static_Discrete_Predicate
(P_Type
));
8193 if Nkind
(LastN
) = N_Range
then
8194 Fold_Uint
(N
, Expr_Value
(High_Bound
(LastN
)), Static
);
8196 Fold_Uint
(N
, Expr_Value
(LastN
), Static
);
8202 Fold_Uint
(N
, Expr_Value
(Hi_Bound
), Static
);
8210 when Attribute_Leading_Part
=>
8213 Eval_Fat
.Leading_Part
8214 (P_Base_Type
, Expr_Value_R
(E1
), Expr_Value
(E2
)),
8221 when Attribute_Length
=> Length
: declare
8225 -- If any index type is a formal type, or derived from one, the
8226 -- bounds are not static. Treating them as static can produce
8227 -- spurious warnings or improper constant folding.
8229 Ind
:= First_Index
(P_Type
);
8230 while Present
(Ind
) loop
8231 if Is_Generic_Type
(Root_Type
(Etype
(Ind
))) then
8240 -- For two compile time values, we can compute length
8242 if Compile_Time_Known_Value
(Lo_Bound
)
8243 and then Compile_Time_Known_Value
(Hi_Bound
)
8246 UI_Max
(0, 1 + (Expr_Value
(Hi_Bound
) - Expr_Value
(Lo_Bound
))),
8250 -- One more case is where Hi_Bound and Lo_Bound are compile-time
8251 -- comparable, and we can figure out the difference between them.
8254 Diff
: aliased Uint
;
8258 Compile_Time_Compare
8259 (Lo_Bound
, Hi_Bound
, Diff
'Access, Assume_Valid
=> False)
8262 Fold_Uint
(N
, Uint_1
, Static
);
8265 Fold_Uint
(N
, Uint_0
, Static
);
8268 if Diff
/= No_Uint
then
8269 Fold_Uint
(N
, Diff
+ 1, Static
);
8282 -- Loop_Entry acts as an alias of a constant initialized to the prefix
8283 -- of the said attribute at the point of entry into the related loop. As
8284 -- such, the attribute reference does not need to be evaluated because
8285 -- the prefix is the one that is evaluted.
8287 when Attribute_Loop_Entry
=>
8294 when Attribute_Machine
=>
8298 (P_Base_Type
, Expr_Value_R
(E1
), Eval_Fat
.Round
, N
),
8305 when Attribute_Machine_Emax
=>
8306 Fold_Uint
(N
, Machine_Emax_Value
(P_Type
), Static
);
8312 when Attribute_Machine_Emin
=>
8313 Fold_Uint
(N
, Machine_Emin_Value
(P_Type
), Static
);
8315 ----------------------
8316 -- Machine_Mantissa --
8317 ----------------------
8319 when Attribute_Machine_Mantissa
=>
8320 Fold_Uint
(N
, Machine_Mantissa_Value
(P_Type
), Static
);
8322 -----------------------
8323 -- Machine_Overflows --
8324 -----------------------
8326 when Attribute_Machine_Overflows
=>
8328 -- Always true for fixed-point
8330 if Is_Fixed_Point_Type
(P_Type
) then
8331 Fold_Uint
(N
, True_Value
, Static
);
8333 -- Floating point case
8337 UI_From_Int
(Boolean'Pos (Machine_Overflows_On_Target
)),
8345 when Attribute_Machine_Radix
=>
8346 if Is_Fixed_Point_Type
(P_Type
) then
8347 if Is_Decimal_Fixed_Point_Type
(P_Type
)
8348 and then Machine_Radix_10
(P_Type
)
8350 Fold_Uint
(N
, Uint_10
, Static
);
8352 Fold_Uint
(N
, Uint_2
, Static
);
8355 -- All floating-point type always have radix 2
8358 Fold_Uint
(N
, Uint_2
, Static
);
8361 ----------------------
8362 -- Machine_Rounding --
8363 ----------------------
8365 -- Note: for the folding case, it is fine to treat Machine_Rounding
8366 -- exactly the same way as Rounding, since this is one of the allowed
8367 -- behaviors, and performance is not an issue here. It might be a bit
8368 -- better to give the same result as it would give at run time, even
8369 -- though the non-determinism is certainly permitted.
8371 when Attribute_Machine_Rounding
=>
8373 (N
, Eval_Fat
.Rounding
(P_Base_Type
, Expr_Value_R
(E1
)), Static
);
8375 --------------------
8376 -- Machine_Rounds --
8377 --------------------
8379 when Attribute_Machine_Rounds
=>
8381 -- Always False for fixed-point
8383 if Is_Fixed_Point_Type
(P_Type
) then
8384 Fold_Uint
(N
, False_Value
, Static
);
8386 -- Else yield proper floating-point result
8390 (N
, UI_From_Int
(Boolean'Pos (Machine_Rounds_On_Target
)),
8398 -- Note: Machine_Size is identical to Object_Size
8400 when Attribute_Machine_Size
=> Machine_Size
: declare
8401 P_TypeA
: constant Entity_Id
:= Underlying_Type
(P_Type
);
8404 if Known_Esize
(P_TypeA
) then
8405 Fold_Uint
(N
, Esize
(P_TypeA
), Static
);
8413 when Attribute_Mantissa
=>
8415 -- Fixed-point mantissa
8417 if Is_Fixed_Point_Type
(P_Type
) then
8419 -- Compile time foldable case
8421 if Compile_Time_Known_Value
(Type_Low_Bound
(P_Type
))
8423 Compile_Time_Known_Value
(Type_High_Bound
(P_Type
))
8425 -- The calculation of the obsolete Ada 83 attribute Mantissa
8426 -- is annoying, because of AI00143, quoted here:
8428 -- !question 84-01-10
8430 -- Consider the model numbers for F:
8432 -- type F is delta 1.0 range -7.0 .. 8.0;
8434 -- The wording requires that F'MANTISSA be the SMALLEST
8435 -- integer number for which each bound of the specified
8436 -- range is either a model number or lies at most small
8437 -- distant from a model number. This means F'MANTISSA
8438 -- is required to be 3 since the range -7.0 .. 7.0 fits
8439 -- in 3 signed bits, and 8 is "at most" 1.0 from a model
8440 -- number, namely, 7. Is this analysis correct? Note that
8441 -- this implies the upper bound of the range is not
8442 -- represented as a model number.
8444 -- !response 84-03-17
8446 -- The analysis is correct. The upper and lower bounds for
8447 -- a fixed point type can lie outside the range of model
8458 LBound
:= Expr_Value_R
(Type_Low_Bound
(P_Type
));
8459 UBound
:= Expr_Value_R
(Type_High_Bound
(P_Type
));
8460 Bound
:= UR_Max
(UR_Abs
(LBound
), UR_Abs
(UBound
));
8461 Max_Man
:= UR_Trunc
(Bound
/ Small_Value
(P_Type
));
8463 -- If the Bound is exactly a model number, i.e. a multiple
8464 -- of Small, then we back it off by one to get the integer
8465 -- value that must be representable.
8467 if Small_Value
(P_Type
) * Max_Man
= Bound
then
8468 Max_Man
:= Max_Man
- 1;
8471 -- Now find corresponding size = Mantissa value
8474 while 2 ** Siz
< Max_Man
loop
8478 Fold_Uint
(N
, Siz
, Static
);
8482 -- The case of dynamic bounds cannot be evaluated at compile
8483 -- time. Instead we use a runtime routine (see Exp_Attr).
8488 -- Floating-point Mantissa
8491 Fold_Uint
(N
, Mantissa
, Static
);
8498 when Attribute_Max
=> Max
:
8500 if Is_Real_Type
(P_Type
) then
8502 (N
, UR_Max
(Expr_Value_R
(E1
), Expr_Value_R
(E2
)), Static
);
8504 Fold_Uint
(N
, UI_Max
(Expr_Value
(E1
), Expr_Value
(E2
)), Static
);
8508 ----------------------------------
8509 -- Max_Alignment_For_Allocation --
8510 ----------------------------------
8512 -- Max_Alignment_For_Allocation is usually the Alignment. However,
8513 -- arrays are allocated with dope, so we need to take into account both
8514 -- the alignment of the array, which comes from the component alignment,
8515 -- and the alignment of the dope. Also, if the alignment is unknown, we
8516 -- use the max (it's OK to be pessimistic).
8518 when Attribute_Max_Alignment_For_Allocation
=>
8520 A
: Uint
:= UI_From_Int
(Ttypes
.Maximum_Alignment
);
8522 if Known_Alignment
(P_Type
) and then
8523 (not Is_Array_Type
(P_Type
) or else Alignment
(P_Type
) > A
)
8525 A
:= Alignment
(P_Type
);
8528 Fold_Uint
(N
, A
, Static
);
8531 ----------------------------------
8532 -- Max_Size_In_Storage_Elements --
8533 ----------------------------------
8535 -- Max_Size_In_Storage_Elements is simply the Size rounded up to a
8536 -- Storage_Unit boundary. We can fold any cases for which the size
8537 -- is known by the front end.
8539 when Attribute_Max_Size_In_Storage_Elements
=>
8540 if Known_Esize
(P_Type
) then
8542 (Esize
(P_Type
) + System_Storage_Unit
- 1) /
8543 System_Storage_Unit
,
8547 --------------------
8548 -- Mechanism_Code --
8549 --------------------
8551 when Attribute_Mechanism_Code
=>
8555 Mech
: Mechanism_Type
;
8559 Mech
:= Mechanism
(P_Entity
);
8562 Val
:= UI_To_Int
(Expr_Value
(E1
));
8564 Formal
:= First_Formal
(P_Entity
);
8565 for J
in 1 .. Val
- 1 loop
8566 Next_Formal
(Formal
);
8568 Mech
:= Mechanism
(Formal
);
8572 Fold_Uint
(N
, UI_From_Int
(Int
(-Mech
)), Static
);
8580 when Attribute_Min
=> Min
:
8582 if Is_Real_Type
(P_Type
) then
8584 (N
, UR_Min
(Expr_Value_R
(E1
), Expr_Value_R
(E2
)), Static
);
8587 (N
, UI_Min
(Expr_Value
(E1
), Expr_Value
(E2
)), Static
);
8595 when Attribute_Mod
=>
8597 (N
, UI_Mod
(Expr_Value
(E1
), Modulus
(P_Base_Type
)), Static
);
8603 when Attribute_Model
=>
8605 (N
, Eval_Fat
.Model
(P_Base_Type
, Expr_Value_R
(E1
)), Static
);
8611 when Attribute_Model_Emin
=>
8612 Fold_Uint
(N
, Model_Emin_Value
(P_Base_Type
), Static
);
8618 when Attribute_Model_Epsilon
=>
8619 Fold_Ureal
(N
, Model_Epsilon_Value
(P_Base_Type
), Static
);
8621 --------------------
8622 -- Model_Mantissa --
8623 --------------------
8625 when Attribute_Model_Mantissa
=>
8626 Fold_Uint
(N
, Model_Mantissa_Value
(P_Base_Type
), Static
);
8632 when Attribute_Model_Small
=>
8633 Fold_Ureal
(N
, Model_Small_Value
(P_Base_Type
), Static
);
8639 when Attribute_Modulus
=>
8640 Fold_Uint
(N
, Modulus
(P_Type
), Static
);
8642 --------------------
8643 -- Null_Parameter --
8644 --------------------
8646 -- Cannot fold, we know the value sort of, but the whole point is
8647 -- that there is no way to talk about this imaginary value except
8648 -- by using the attribute, so we leave it the way it is.
8650 when Attribute_Null_Parameter
=>
8657 -- The Object_Size attribute for a type returns the Esize of the
8658 -- type and can be folded if this value is known.
8660 when Attribute_Object_Size
=> Object_Size
: declare
8661 P_TypeA
: constant Entity_Id
:= Underlying_Type
(P_Type
);
8664 if Known_Esize
(P_TypeA
) then
8665 Fold_Uint
(N
, Esize
(P_TypeA
), Static
);
8669 ----------------------
8670 -- Overlaps_Storage --
8671 ----------------------
8673 when Attribute_Overlaps_Storage
=>
8676 -------------------------
8677 -- Passed_By_Reference --
8678 -------------------------
8680 -- Scalar types are never passed by reference
8682 when Attribute_Passed_By_Reference
=>
8683 Fold_Uint
(N
, False_Value
, Static
);
8689 when Attribute_Pos
=>
8690 Fold_Uint
(N
, Expr_Value
(E1
), Static
);
8696 when Attribute_Pred
=> Pred
:
8698 -- Floating-point case
8700 if Is_Floating_Point_Type
(P_Type
) then
8702 (N
, Eval_Fat
.Pred
(P_Base_Type
, Expr_Value_R
(E1
)), Static
);
8706 elsif Is_Fixed_Point_Type
(P_Type
) then
8708 (N
, Expr_Value_R
(E1
) - Small_Value
(P_Type
), True);
8710 -- Modular integer case (wraps)
8712 elsif Is_Modular_Integer_Type
(P_Type
) then
8713 Fold_Uint
(N
, (Expr_Value
(E1
) - 1) mod Modulus
(P_Type
), Static
);
8715 -- Other scalar cases
8718 pragma Assert
(Is_Scalar_Type
(P_Type
));
8720 if Is_Enumeration_Type
(P_Type
)
8721 and then Expr_Value
(E1
) =
8722 Expr_Value
(Type_Low_Bound
(P_Base_Type
))
8724 Apply_Compile_Time_Constraint_Error
8725 (N
, "Pred of `&''First`",
8726 CE_Overflow_Check_Failed
,
8728 Warn
=> not Static
);
8734 Fold_Uint
(N
, Expr_Value
(E1
) - 1, Static
);
8742 -- No processing required, because by this stage, Range has been
8743 -- replaced by First .. Last, so this branch can never be taken.
8745 when Attribute_Range
=>
8746 raise Program_Error
;
8752 when Attribute_Range_Length
=>
8755 -- Can fold if both bounds are compile time known
8757 if Compile_Time_Known_Value
(Hi_Bound
)
8758 and then Compile_Time_Known_Value
(Lo_Bound
)
8762 (0, Expr_Value
(Hi_Bound
) - Expr_Value
(Lo_Bound
) + 1),
8766 -- One more case is where Hi_Bound and Lo_Bound are compile-time
8767 -- comparable, and we can figure out the difference between them.
8770 Diff
: aliased Uint
;
8774 Compile_Time_Compare
8775 (Lo_Bound
, Hi_Bound
, Diff
'Access, Assume_Valid
=> False)
8778 Fold_Uint
(N
, Uint_1
, Static
);
8781 Fold_Uint
(N
, Uint_0
, Static
);
8784 if Diff
/= No_Uint
then
8785 Fold_Uint
(N
, Diff
+ 1, Static
);
8797 when Attribute_Ref
=>
8798 Fold_Uint
(N
, Expr_Value
(E1
), Static
);
8804 when Attribute_Remainder
=> Remainder
: declare
8805 X
: constant Ureal
:= Expr_Value_R
(E1
);
8806 Y
: constant Ureal
:= Expr_Value_R
(E2
);
8809 if UR_Is_Zero
(Y
) then
8810 Apply_Compile_Time_Constraint_Error
8811 (N
, "division by zero in Remainder",
8812 CE_Overflow_Check_Failed
,
8813 Warn
=> not Static
);
8819 Fold_Ureal
(N
, Eval_Fat
.Remainder
(P_Base_Type
, X
, Y
), Static
);
8826 when Attribute_Restriction_Set
=> Restriction_Set
: declare
8828 Rewrite
(N
, New_Occurrence_Of
(Standard_False
, Loc
));
8829 Set_Is_Static_Expression
(N
);
8830 end Restriction_Set
;
8836 when Attribute_Round
=> Round
:
8842 -- First we get the (exact result) in units of small
8844 Sr
:= Expr_Value_R
(E1
) / Small_Value
(C_Type
);
8846 -- Now round that exactly to an integer
8848 Si
:= UR_To_Uint
(Sr
);
8850 -- Finally the result is obtained by converting back to real
8852 Fold_Ureal
(N
, Si
* Small_Value
(C_Type
), Static
);
8859 when Attribute_Rounding
=>
8861 (N
, Eval_Fat
.Rounding
(P_Base_Type
, Expr_Value_R
(E1
)), Static
);
8867 when Attribute_Safe_Emax
=>
8868 Fold_Uint
(N
, Safe_Emax_Value
(P_Type
), Static
);
8874 when Attribute_Safe_First
=>
8875 Fold_Ureal
(N
, Safe_First_Value
(P_Type
), Static
);
8881 when Attribute_Safe_Large
=>
8882 if Is_Fixed_Point_Type
(P_Type
) then
8884 (N
, Expr_Value_R
(Type_High_Bound
(P_Base_Type
)), Static
);
8886 Fold_Ureal
(N
, Safe_Last_Value
(P_Type
), Static
);
8893 when Attribute_Safe_Last
=>
8894 Fold_Ureal
(N
, Safe_Last_Value
(P_Type
), Static
);
8900 when Attribute_Safe_Small
=>
8902 -- In Ada 95, the old Ada 83 attribute Safe_Small is redundant
8903 -- for fixed-point, since is the same as Small, but we implement
8904 -- it for backwards compatibility.
8906 if Is_Fixed_Point_Type
(P_Type
) then
8907 Fold_Ureal
(N
, Small_Value
(P_Type
), Static
);
8909 -- Ada 83 Safe_Small for floating-point cases
8912 Fold_Ureal
(N
, Model_Small_Value
(P_Type
), Static
);
8919 when Attribute_Scale
=>
8920 Fold_Uint
(N
, Scale_Value
(P_Type
), Static
);
8926 when Attribute_Scaling
=>
8930 (P_Base_Type
, Expr_Value_R
(E1
), Expr_Value
(E2
)),
8937 when Attribute_Signed_Zeros
=>
8939 (N
, UI_From_Int
(Boolean'Pos (Has_Signed_Zeros
(P_Type
))), Static
);
8945 -- Size attribute returns the RM size. All scalar types can be folded,
8946 -- as well as any types for which the size is known by the front end,
8947 -- including any type for which a size attribute is specified. This is
8948 -- one of the places where it is annoying that a size of zero means two
8949 -- things (zero size for scalars, unspecified size for non-scalars).
8951 when Attribute_Size | Attribute_VADS_Size
=> Size
: declare
8952 P_TypeA
: constant Entity_Id
:= Underlying_Type
(P_Type
);
8955 if Is_Scalar_Type
(P_TypeA
) or else RM_Size
(P_TypeA
) /= Uint_0
then
8959 if Id
= Attribute_VADS_Size
or else Use_VADS_Size
then
8961 S
: constant Node_Id
:= Size_Clause
(P_TypeA
);
8964 -- If a size clause applies, then use the size from it.
8965 -- This is one of the rare cases where we can use the
8966 -- Size_Clause field for a subtype when Has_Size_Clause
8967 -- is False. Consider:
8969 -- type x is range 1 .. 64;
8970 -- for x'size use 12;
8971 -- subtype y is x range 0 .. 3;
8973 -- Here y has a size clause inherited from x, but normally
8974 -- it does not apply, and y'size is 2. However, y'VADS_Size
8975 -- is indeed 12 and not 2.
8978 and then Is_OK_Static_Expression
(Expression
(S
))
8980 Fold_Uint
(N
, Expr_Value
(Expression
(S
)), Static
);
8982 -- If no size is specified, then we simply use the object
8983 -- size in the VADS_Size case (e.g. Natural'Size is equal
8984 -- to Integer'Size, not one less).
8987 Fold_Uint
(N
, Esize
(P_TypeA
), Static
);
8991 -- Normal case (Size) in which case we want the RM_Size
8994 Fold_Uint
(N
, RM_Size
(P_TypeA
), Static
);
9003 when Attribute_Small
=>
9005 -- The floating-point case is present only for Ada 83 compatibility.
9006 -- Note that strictly this is an illegal addition, since we are
9007 -- extending an Ada 95 defined attribute, but we anticipate an
9008 -- ARG ruling that will permit this.
9010 if Is_Floating_Point_Type
(P_Type
) then
9012 -- Ada 83 attribute is defined as (RM83 3.5.8)
9014 -- T'Small = 2.0**(-T'Emax - 1)
9018 -- T'Emax = 4 * T'Mantissa
9020 Fold_Ureal
(N
, Ureal_2
** ((-(4 * Mantissa
)) - 1), Static
);
9022 -- Normal Ada 95 fixed-point case
9025 Fold_Ureal
(N
, Small_Value
(P_Type
), True);
9032 when Attribute_Stream_Size
=>
9039 when Attribute_Succ
=> Succ
:
9041 -- Floating-point case
9043 if Is_Floating_Point_Type
(P_Type
) then
9045 (N
, Eval_Fat
.Succ
(P_Base_Type
, Expr_Value_R
(E1
)), Static
);
9049 elsif Is_Fixed_Point_Type
(P_Type
) then
9050 Fold_Ureal
(N
, Expr_Value_R
(E1
) + Small_Value
(P_Type
), Static
);
9052 -- Modular integer case (wraps)
9054 elsif Is_Modular_Integer_Type
(P_Type
) then
9055 Fold_Uint
(N
, (Expr_Value
(E1
) + 1) mod Modulus
(P_Type
), Static
);
9057 -- Other scalar cases
9060 pragma Assert
(Is_Scalar_Type
(P_Type
));
9062 if Is_Enumeration_Type
(P_Type
)
9063 and then Expr_Value
(E1
) =
9064 Expr_Value
(Type_High_Bound
(P_Base_Type
))
9066 Apply_Compile_Time_Constraint_Error
9067 (N
, "Succ of `&''Last`",
9068 CE_Overflow_Check_Failed
,
9070 Warn
=> not Static
);
9075 Fold_Uint
(N
, Expr_Value
(E1
) + 1, Static
);
9084 when Attribute_Truncation
=>
9087 Eval_Fat
.Truncation
(P_Base_Type
, Expr_Value_R
(E1
)),
9094 when Attribute_Type_Class
=> Type_Class
: declare
9095 Typ
: constant Entity_Id
:= Underlying_Type
(P_Base_Type
);
9099 if Is_Descendent_Of_Address
(Typ
) then
9100 Id
:= RE_Type_Class_Address
;
9102 elsif Is_Enumeration_Type
(Typ
) then
9103 Id
:= RE_Type_Class_Enumeration
;
9105 elsif Is_Integer_Type
(Typ
) then
9106 Id
:= RE_Type_Class_Integer
;
9108 elsif Is_Fixed_Point_Type
(Typ
) then
9109 Id
:= RE_Type_Class_Fixed_Point
;
9111 elsif Is_Floating_Point_Type
(Typ
) then
9112 Id
:= RE_Type_Class_Floating_Point
;
9114 elsif Is_Array_Type
(Typ
) then
9115 Id
:= RE_Type_Class_Array
;
9117 elsif Is_Record_Type
(Typ
) then
9118 Id
:= RE_Type_Class_Record
;
9120 elsif Is_Access_Type
(Typ
) then
9121 Id
:= RE_Type_Class_Access
;
9123 elsif Is_Enumeration_Type
(Typ
) then
9124 Id
:= RE_Type_Class_Enumeration
;
9126 elsif Is_Task_Type
(Typ
) then
9127 Id
:= RE_Type_Class_Task
;
9129 -- We treat protected types like task types. It would make more
9130 -- sense to have another enumeration value, but after all the
9131 -- whole point of this feature is to be exactly DEC compatible,
9132 -- and changing the type Type_Class would not meet this requirement.
9134 elsif Is_Protected_Type
(Typ
) then
9135 Id
:= RE_Type_Class_Task
;
9137 -- Not clear if there are any other possibilities, but if there
9138 -- are, then we will treat them as the address case.
9141 Id
:= RE_Type_Class_Address
;
9144 Rewrite
(N
, New_Occurrence_Of
(RTE
(Id
), Loc
));
9147 -----------------------
9148 -- Unbiased_Rounding --
9149 -----------------------
9151 when Attribute_Unbiased_Rounding
=>
9154 Eval_Fat
.Unbiased_Rounding
(P_Base_Type
, Expr_Value_R
(E1
)),
9157 -------------------------
9158 -- Unconstrained_Array --
9159 -------------------------
9161 when Attribute_Unconstrained_Array
=> Unconstrained_Array
: declare
9162 Typ
: constant Entity_Id
:= Underlying_Type
(P_Type
);
9165 Rewrite
(N
, New_Occurrence_Of
(
9167 Is_Array_Type
(P_Type
)
9168 and then not Is_Constrained
(Typ
)), Loc
));
9170 -- Analyze and resolve as boolean, note that this attribute is
9171 -- a static attribute in GNAT.
9173 Analyze_And_Resolve
(N
, Standard_Boolean
);
9175 Set_Is_Static_Expression
(N
, True);
9176 end Unconstrained_Array
;
9178 -- Attribute Update is never static
9180 when Attribute_Update
=>
9187 -- Processing is shared with Size
9193 when Attribute_Val
=> Val
:
9195 if Expr_Value
(E1
) < Expr_Value
(Type_Low_Bound
(P_Base_Type
))
9197 Expr_Value
(E1
) > Expr_Value
(Type_High_Bound
(P_Base_Type
))
9199 Apply_Compile_Time_Constraint_Error
9200 (N
, "Val expression out of range",
9201 CE_Range_Check_Failed
,
9202 Warn
=> not Static
);
9208 Fold_Uint
(N
, Expr_Value
(E1
), Static
);
9216 -- The Value_Size attribute for a type returns the RM size of the type.
9217 -- This an always be folded for scalar types, and can also be folded for
9218 -- non-scalar types if the size is set. This is one of the places where
9219 -- it is annoying that a size of zero means two things!
9221 when Attribute_Value_Size
=> Value_Size
: declare
9222 P_TypeA
: constant Entity_Id
:= Underlying_Type
(P_Type
);
9224 if Is_Scalar_Type
(P_TypeA
) or else RM_Size
(P_TypeA
) /= Uint_0
then
9225 Fold_Uint
(N
, RM_Size
(P_TypeA
), Static
);
9233 -- Version can never be static
9235 when Attribute_Version
=>
9242 -- Wide_Image is a scalar attribute, but is never static, because it
9243 -- is not a static function (having a non-scalar argument (RM 4.9(22))
9245 when Attribute_Wide_Image
=>
9248 ---------------------
9249 -- Wide_Wide_Image --
9250 ---------------------
9252 -- Wide_Wide_Image is a scalar attribute but is never static, because it
9253 -- is not a static function (having a non-scalar argument (RM 4.9(22)).
9255 when Attribute_Wide_Wide_Image
=>
9258 ---------------------
9259 -- Wide_Wide_Width --
9260 ---------------------
9262 -- Processing for Wide_Wide_Width is combined with Width
9268 -- Processing for Wide_Width is combined with Width
9274 -- This processing also handles the case of Wide_[Wide_]Width
9276 when Attribute_Width |
9277 Attribute_Wide_Width |
9278 Attribute_Wide_Wide_Width
=> Width
:
9280 if Compile_Time_Known_Bounds
(P_Type
) then
9282 -- Floating-point types
9284 if Is_Floating_Point_Type
(P_Type
) then
9286 -- Width is zero for a null range (RM 3.5 (38))
9288 if Expr_Value_R
(Type_High_Bound
(P_Type
)) <
9289 Expr_Value_R
(Type_Low_Bound
(P_Type
))
9291 Fold_Uint
(N
, Uint_0
, Static
);
9294 -- For floating-point, we have +N.dddE+nnn where length
9295 -- of ddd is determined by type'Digits - 1, but is one
9296 -- if Digits is one (RM 3.5 (33)).
9298 -- nnn is set to 2 for Short_Float and Float (32 bit
9299 -- floats), and 3 for Long_Float and Long_Long_Float.
9300 -- For machines where Long_Long_Float is the IEEE
9301 -- extended precision type, the exponent takes 4 digits.
9305 Int
'Max (2, UI_To_Int
(Digits_Value
(P_Type
)));
9308 if Esize
(P_Type
) <= 32 then
9310 elsif Esize
(P_Type
) = 64 then
9316 Fold_Uint
(N
, UI_From_Int
(Len
), Static
);
9320 -- Fixed-point types
9322 elsif Is_Fixed_Point_Type
(P_Type
) then
9324 -- Width is zero for a null range (RM 3.5 (38))
9326 if Expr_Value
(Type_High_Bound
(P_Type
)) <
9327 Expr_Value
(Type_Low_Bound
(P_Type
))
9329 Fold_Uint
(N
, Uint_0
, Static
);
9331 -- The non-null case depends on the specific real type
9334 -- For fixed-point type width is Fore + 1 + Aft (RM 3.5(34))
9337 (N
, UI_From_Int
(Fore_Value
+ 1) + Aft_Value
(P_Type
),
9345 R
: constant Entity_Id
:= Root_Type
(P_Type
);
9346 Lo
: constant Uint
:= Expr_Value
(Type_Low_Bound
(P_Type
));
9347 Hi
: constant Uint
:= Expr_Value
(Type_High_Bound
(P_Type
));
9360 -- Width for types derived from Standard.Character
9361 -- and Standard.Wide_[Wide_]Character.
9363 elsif Is_Standard_Character_Type
(P_Type
) then
9366 -- Set W larger if needed
9368 for J
in UI_To_Int
(Lo
) .. UI_To_Int
(Hi
) loop
9370 -- All wide characters look like Hex_hhhhhhhh
9374 -- No need to compute this more than once
9379 C
:= Character'Val (J
);
9381 -- Test for all cases where Character'Image
9382 -- yields an image that is longer than three
9383 -- characters. First the cases of Reserved_xxx
9384 -- names (length = 12).
9387 when Reserved_128 | Reserved_129 |
9388 Reserved_132 | Reserved_153
9391 when BS | HT | LF | VT | FF | CR |
9392 SO | SI | EM | FS | GS | RS |
9393 US | RI | MW | ST | PM
9396 when NUL | SOH | STX | ETX | EOT |
9397 ENQ | ACK | BEL | DLE | DC1 |
9398 DC2 | DC3 | DC4 | NAK | SYN |
9399 ETB | CAN | SUB | ESC | DEL |
9400 BPH | NBH | NEL | SSA | ESA |
9401 HTS | HTJ | VTS | PLD | PLU |
9402 SS2 | SS3 | DCS | PU1 | PU2 |
9403 STS | CCH | SPA | EPA | SOS |
9404 SCI | CSI | OSC | APC
9407 when Space
.. Tilde |
9408 No_Break_Space
.. LC_Y_Diaeresis
9410 -- Special case of soft hyphen in Ada 2005
9412 if C
= Character'Val (16#AD#
)
9413 and then Ada_Version
>= Ada_2005
9421 W
:= Int
'Max (W
, Wt
);
9425 -- Width for types derived from Standard.Boolean
9427 elsif R
= Standard_Boolean
then
9434 -- Width for integer types
9436 elsif Is_Integer_Type
(P_Type
) then
9437 T
:= UI_Max
(abs Lo
, abs Hi
);
9445 -- User declared enum type with discard names
9447 elsif Discard_Names
(R
) then
9449 -- If range is null, result is zero, that has already
9450 -- been dealt with, so what we need is the power of ten
9451 -- that accomodates the Pos of the largest value, which
9452 -- is the high bound of the range + one for the space.
9461 -- Only remaining possibility is user declared enum type
9462 -- with normal case of Discard_Names not active.
9465 pragma Assert
(Is_Enumeration_Type
(P_Type
));
9468 L
:= First_Literal
(P_Type
);
9469 while Present
(L
) loop
9471 -- Only pay attention to in range characters
9473 if Lo
<= Enumeration_Pos
(L
)
9474 and then Enumeration_Pos
(L
) <= Hi
9476 -- For Width case, use decoded name
9478 if Id
= Attribute_Width
then
9479 Get_Decoded_Name_String
(Chars
(L
));
9480 Wt
:= Nat
(Name_Len
);
9482 -- For Wide_[Wide_]Width, use encoded name, and
9483 -- then adjust for the encoding.
9486 Get_Name_String
(Chars
(L
));
9488 -- Character literals are always of length 3
9490 if Name_Buffer
(1) = 'Q' then
9493 -- Otherwise loop to adjust for upper/wide chars
9496 Wt
:= Nat
(Name_Len
);
9498 for J
in 1 .. Name_Len
loop
9499 if Name_Buffer
(J
) = 'U' then
9501 elsif Name_Buffer
(J
) = 'W' then
9508 W
:= Int
'Max (W
, Wt
);
9515 Fold_Uint
(N
, UI_From_Int
(W
), Static
);
9521 -- The following attributes denote functions that cannot be folded
9523 when Attribute_From_Any |
9525 Attribute_TypeCode
=>
9528 -- The following attributes can never be folded, and furthermore we
9529 -- should not even have entered the case statement for any of these.
9530 -- Note that in some cases, the values have already been folded as
9531 -- a result of the processing in Analyze_Attribute.
9533 when Attribute_Abort_Signal |
9536 Attribute_Address_Size |
9537 Attribute_Asm_Input |
9538 Attribute_Asm_Output |
9540 Attribute_Bit_Order |
9541 Attribute_Bit_Position |
9542 Attribute_Callable |
9545 Attribute_Code_Address |
9546 Attribute_Compiler_Version |
9548 Attribute_Default_Bit_Order |
9549 Attribute_Elaborated |
9550 Attribute_Elab_Body |
9551 Attribute_Elab_Spec |
9552 Attribute_Elab_Subp_Body |
9554 Attribute_External_Tag |
9555 Attribute_Fast_Math |
9556 Attribute_First_Bit |
9558 Attribute_Last_Bit |
9559 Attribute_Library_Level |
9560 Attribute_Maximum_Alignment |
9563 Attribute_Partition_ID |
9564 Attribute_Pool_Address |
9565 Attribute_Position |
9566 Attribute_Priority |
9569 Attribute_Scalar_Storage_Order |
9570 Attribute_Simple_Storage_Pool |
9571 Attribute_Storage_Pool |
9572 Attribute_Storage_Size |
9573 Attribute_Storage_Unit |
9574 Attribute_Stub_Type |
9575 Attribute_System_Allocator_Alignment |
9577 Attribute_Target_Name |
9578 Attribute_Terminated |
9579 Attribute_To_Address |
9580 Attribute_Type_Key |
9581 Attribute_UET_Address |
9582 Attribute_Unchecked_Access |
9583 Attribute_Universal_Literal_String |
9584 Attribute_Unrestricted_Access |
9586 Attribute_Valid_Scalars |
9588 Attribute_Wchar_T_Size |
9589 Attribute_Wide_Value |
9590 Attribute_Wide_Wide_Value |
9591 Attribute_Word_Size |
9594 raise Program_Error
;
9597 -- At the end of the case, one more check. If we did a static evaluation
9598 -- so that the result is now a literal, then set Is_Static_Expression
9599 -- in the constant only if the prefix type is a static subtype. For
9600 -- non-static subtypes, the folding is still OK, but not static.
9602 -- An exception is the GNAT attribute Constrained_Array which is
9603 -- defined to be a static attribute in all cases.
9605 if Nkind_In
(N
, N_Integer_Literal
,
9607 N_Character_Literal
,
9609 or else (Is_Entity_Name
(N
)
9610 and then Ekind
(Entity
(N
)) = E_Enumeration_Literal
)
9612 Set_Is_Static_Expression
(N
, Static
);
9614 -- If this is still an attribute reference, then it has not been folded
9615 -- and that means that its expressions are in a non-static context.
9617 elsif Nkind
(N
) = N_Attribute_Reference
then
9620 -- Note: the else case not covered here are odd cases where the
9621 -- processing has transformed the attribute into something other
9622 -- than a constant. Nothing more to do in such cases.
9629 ------------------------------
9630 -- Is_Anonymous_Tagged_Base --
9631 ------------------------------
9633 function Is_Anonymous_Tagged_Base
9635 Typ
: Entity_Id
) return Boolean
9639 Anon
= Current_Scope
9640 and then Is_Itype
(Anon
)
9641 and then Associated_Node_For_Itype
(Anon
) = Parent
(Typ
);
9642 end Is_Anonymous_Tagged_Base
;
9644 --------------------------------
9645 -- Name_Implies_Lvalue_Prefix --
9646 --------------------------------
9648 function Name_Implies_Lvalue_Prefix
(Nam
: Name_Id
) return Boolean is
9649 pragma Assert
(Is_Attribute_Name
(Nam
));
9651 return Attribute_Name_Implies_Lvalue_Prefix
(Get_Attribute_Id
(Nam
));
9652 end Name_Implies_Lvalue_Prefix
;
9654 -----------------------
9655 -- Resolve_Attribute --
9656 -----------------------
9658 procedure Resolve_Attribute
(N
: Node_Id
; Typ
: Entity_Id
) is
9659 Loc
: constant Source_Ptr
:= Sloc
(N
);
9660 P
: constant Node_Id
:= Prefix
(N
);
9661 Aname
: constant Name_Id
:= Attribute_Name
(N
);
9662 Attr_Id
: constant Attribute_Id
:= Get_Attribute_Id
(Aname
);
9663 Btyp
: constant Entity_Id
:= Base_Type
(Typ
);
9664 Des_Btyp
: Entity_Id
;
9665 Index
: Interp_Index
;
9667 Nom_Subt
: Entity_Id
;
9669 procedure Accessibility_Message
;
9670 -- Error, or warning within an instance, if the static accessibility
9671 -- rules of 3.10.2 are violated.
9673 ---------------------------
9674 -- Accessibility_Message --
9675 ---------------------------
9677 procedure Accessibility_Message
is
9678 Indic
: Node_Id
:= Parent
(Parent
(N
));
9681 -- In an instance, this is a runtime check, but one we
9682 -- know will fail, so generate an appropriate warning.
9684 if In_Instance_Body
then
9685 Error_Msg_Warn
:= SPARK_Mode
/= On
;
9687 ("non-local pointer cannot point to local object<<", P
);
9688 Error_Msg_F
("\Program_Error [<<", P
);
9690 Make_Raise_Program_Error
(Loc
,
9691 Reason
=> PE_Accessibility_Check_Failed
));
9696 Error_Msg_F
("non-local pointer cannot point to local object", P
);
9698 -- Check for case where we have a missing access definition
9700 if Is_Record_Type
(Current_Scope
)
9702 Nkind_In
(Parent
(N
), N_Discriminant_Association
,
9703 N_Index_Or_Discriminant_Constraint
)
9705 Indic
:= Parent
(Parent
(N
));
9706 while Present
(Indic
)
9707 and then Nkind
(Indic
) /= N_Subtype_Indication
9709 Indic
:= Parent
(Indic
);
9712 if Present
(Indic
) then
9714 ("\use an access definition for" &
9715 " the access discriminant of&",
9716 N
, Entity
(Subtype_Mark
(Indic
)));
9720 end Accessibility_Message
;
9722 -- Start of processing for Resolve_Attribute
9725 -- If error during analysis, no point in continuing, except for array
9726 -- types, where we get better recovery by using unconstrained indexes
9727 -- than nothing at all (see Check_Array_Type).
9730 and then Attr_Id
/= Attribute_First
9731 and then Attr_Id
/= Attribute_Last
9732 and then Attr_Id
/= Attribute_Length
9733 and then Attr_Id
/= Attribute_Range
9738 -- If attribute was universal type, reset to actual type
9740 if Etype
(N
) = Universal_Integer
9741 or else Etype
(N
) = Universal_Real
9746 -- Remaining processing depends on attribute
9754 -- For access attributes, if the prefix denotes an entity, it is
9755 -- interpreted as a name, never as a call. It may be overloaded,
9756 -- in which case resolution uses the profile of the context type.
9757 -- Otherwise prefix must be resolved.
9759 when Attribute_Access
9760 | Attribute_Unchecked_Access
9761 | Attribute_Unrestricted_Access
=>
9765 if Is_Variable
(P
) then
9766 Note_Possible_Modification
(P
, Sure
=> False);
9769 -- The following comes from a query concerning improper use of
9770 -- universal_access in equality tests involving anonymous access
9771 -- types. Another good reason for 'Ref, but for now disable the
9772 -- test, which breaks several filed tests???
9774 if Ekind
(Typ
) = E_Anonymous_Access_Type
9775 and then Nkind_In
(Parent
(N
), N_Op_Eq
, N_Op_Ne
)
9778 Error_Msg_N
("need unique type to resolve 'Access", N
);
9779 Error_Msg_N
("\qualify attribute with some access type", N
);
9782 -- Case where prefix is an entity name
9784 if Is_Entity_Name
(P
) then
9786 -- Deal with case where prefix itself is overloaded
9788 if Is_Overloaded
(P
) then
9789 Get_First_Interp
(P
, Index
, It
);
9790 while Present
(It
.Nam
) loop
9791 if Type_Conformant
(Designated_Type
(Typ
), It
.Nam
) then
9792 Set_Entity
(P
, It
.Nam
);
9794 -- The prefix is definitely NOT overloaded anymore at
9795 -- this point, so we reset the Is_Overloaded flag to
9796 -- avoid any confusion when reanalyzing the node.
9798 Set_Is_Overloaded
(P
, False);
9799 Set_Is_Overloaded
(N
, False);
9800 Generate_Reference
(Entity
(P
), P
);
9804 Get_Next_Interp
(Index
, It
);
9807 -- If Prefix is a subprogram name, this reference freezes:
9809 -- If it is a type, there is nothing to resolve.
9810 -- If it is an object, complete its resolution.
9812 elsif Is_Overloadable
(Entity
(P
)) then
9814 -- Avoid insertion of freeze actions in spec expression mode
9816 if not In_Spec_Expression
then
9817 Freeze_Before
(N
, Entity
(P
));
9820 -- Nothing to do if prefix is a type name
9822 elsif Is_Type
(Entity
(P
)) then
9825 -- Otherwise non-overloaded other case, resolve the prefix
9831 -- Some further error checks
9833 Error_Msg_Name_1
:= Aname
;
9835 if not Is_Entity_Name
(P
) then
9838 elsif Is_Overloadable
(Entity
(P
))
9839 and then Is_Abstract_Subprogram
(Entity
(P
))
9841 Error_Msg_F
("prefix of % attribute cannot be abstract", P
);
9842 Set_Etype
(N
, Any_Type
);
9844 elsif Ekind
(Entity
(P
)) = E_Enumeration_Literal
then
9846 ("prefix of % attribute cannot be enumeration literal", P
);
9847 Set_Etype
(N
, Any_Type
);
9849 -- An attempt to take 'Access of a function that renames an
9850 -- enumeration literal. Issue a specialized error message.
9852 elsif Ekind
(Entity
(P
)) = E_Function
9853 and then Present
(Alias
(Entity
(P
)))
9854 and then Ekind
(Alias
(Entity
(P
))) = E_Enumeration_Literal
9857 ("prefix of % attribute cannot be function renaming "
9858 & "an enumeration literal", P
);
9859 Set_Etype
(N
, Any_Type
);
9861 elsif Convention
(Entity
(P
)) = Convention_Intrinsic
then
9862 Error_Msg_F
("prefix of % attribute cannot be intrinsic", P
);
9863 Set_Etype
(N
, Any_Type
);
9866 -- Assignments, return statements, components of aggregates,
9867 -- generic instantiations will require convention checks if
9868 -- the type is an access to subprogram. Given that there will
9869 -- also be accessibility checks on those, this is where the
9870 -- checks can eventually be centralized ???
9872 if Ekind_In
(Btyp
, E_Access_Subprogram_Type
,
9873 E_Anonymous_Access_Subprogram_Type
,
9874 E_Access_Protected_Subprogram_Type
,
9875 E_Anonymous_Access_Protected_Subprogram_Type
)
9877 -- Deal with convention mismatch
9879 if Convention
(Designated_Type
(Btyp
)) /=
9880 Convention
(Entity
(P
))
9883 ("subprogram & has wrong convention", P
, Entity
(P
));
9884 Error_Msg_Sloc
:= Sloc
(Btyp
);
9885 Error_Msg_FE
("\does not match & declared#", P
, Btyp
);
9887 if not Is_Itype
(Btyp
)
9888 and then not Has_Convention_Pragma
(Btyp
)
9891 ("\probable missing pragma Convention for &",
9896 Check_Subtype_Conformant
9897 (New_Id
=> Entity
(P
),
9898 Old_Id
=> Designated_Type
(Btyp
),
9902 if Attr_Id
= Attribute_Unchecked_Access
then
9903 Error_Msg_Name_1
:= Aname
;
9905 ("attribute% cannot be applied to a subprogram", P
);
9907 elsif Aname
= Name_Unrestricted_Access
then
9908 null; -- Nothing to check
9910 -- Check the static accessibility rule of 3.10.2(32).
9911 -- This rule also applies within the private part of an
9912 -- instantiation. This rule does not apply to anonymous
9913 -- access-to-subprogram types in access parameters.
9915 elsif Attr_Id
= Attribute_Access
9916 and then not In_Instance_Body
9918 (Ekind
(Btyp
) = E_Access_Subprogram_Type
9919 or else Is_Local_Anonymous_Access
(Btyp
))
9920 and then Subprogram_Access_Level
(Entity
(P
)) >
9921 Type_Access_Level
(Btyp
)
9924 ("subprogram must not be deeper than access type", P
);
9926 -- Check the restriction of 3.10.2(32) that disallows the
9927 -- access attribute within a generic body when the ultimate
9928 -- ancestor of the type of the attribute is declared outside
9929 -- of the generic unit and the subprogram is declared within
9930 -- that generic unit. This includes any such attribute that
9931 -- occurs within the body of a generic unit that is a child
9932 -- of the generic unit where the subprogram is declared.
9934 -- The rule also prohibits applying the attribute when the
9935 -- access type is a generic formal access type (since the
9936 -- level of the actual type is not known). This restriction
9937 -- does not apply when the attribute type is an anonymous
9938 -- access-to-subprogram type. Note that this check was
9939 -- revised by AI-229, because the originally Ada 95 rule
9940 -- was too lax. The original rule only applied when the
9941 -- subprogram was declared within the body of the generic,
9942 -- which allowed the possibility of dangling references).
9943 -- The rule was also too strict in some case, in that it
9944 -- didn't permit the access to be declared in the generic
9945 -- spec, whereas the revised rule does (as long as it's not
9948 -- There are a couple of subtleties of the test for applying
9949 -- the check that are worth noting. First, we only apply it
9950 -- when the levels of the subprogram and access type are the
9951 -- same (the case where the subprogram is statically deeper
9952 -- was applied above, and the case where the type is deeper
9953 -- is always safe). Second, we want the check to apply
9954 -- within nested generic bodies and generic child unit
9955 -- bodies, but not to apply to an attribute that appears in
9956 -- the generic unit's specification. This is done by testing
9957 -- that the attribute's innermost enclosing generic body is
9958 -- not the same as the innermost generic body enclosing the
9959 -- generic unit where the subprogram is declared (we don't
9960 -- want the check to apply when the access attribute is in
9961 -- the spec and there's some other generic body enclosing
9962 -- generic). Finally, there's no point applying the check
9963 -- when within an instance, because any violations will have
9964 -- been caught by the compilation of the generic unit.
9966 -- We relax this check in Relaxed_RM_Semantics mode for
9967 -- compatibility with legacy code for use by Ada source
9968 -- code analyzers (e.g. CodePeer).
9970 elsif Attr_Id
= Attribute_Access
9971 and then not Relaxed_RM_Semantics
9972 and then not In_Instance
9973 and then Present
(Enclosing_Generic_Unit
(Entity
(P
)))
9974 and then Present
(Enclosing_Generic_Body
(N
))
9975 and then Enclosing_Generic_Body
(N
) /=
9976 Enclosing_Generic_Body
9977 (Enclosing_Generic_Unit
(Entity
(P
)))
9978 and then Subprogram_Access_Level
(Entity
(P
)) =
9979 Type_Access_Level
(Btyp
)
9980 and then Ekind
(Btyp
) /=
9981 E_Anonymous_Access_Subprogram_Type
9982 and then Ekind
(Btyp
) /=
9983 E_Anonymous_Access_Protected_Subprogram_Type
9985 -- The attribute type's ultimate ancestor must be
9986 -- declared within the same generic unit as the
9987 -- subprogram is declared. The error message is
9988 -- specialized to say "ancestor" for the case where the
9989 -- access type is not its own ancestor, since saying
9990 -- simply "access type" would be very confusing.
9992 if Enclosing_Generic_Unit
(Entity
(P
)) /=
9993 Enclosing_Generic_Unit
(Root_Type
(Btyp
))
9996 ("''Access attribute not allowed in generic body",
9999 if Root_Type
(Btyp
) = Btyp
then
10002 "access type & is declared outside " &
10003 "generic unit (RM 3.10.2(32))", N
, Btyp
);
10006 ("\because ancestor of " &
10007 "access type & is declared outside " &
10008 "generic unit (RM 3.10.2(32))", N
, Btyp
);
10012 ("\move ''Access to private part, or " &
10013 "(Ada 2005) use anonymous access type instead of &",
10016 -- If the ultimate ancestor of the attribute's type is
10017 -- a formal type, then the attribute is illegal because
10018 -- the actual type might be declared at a higher level.
10019 -- The error message is specialized to say "ancestor"
10020 -- for the case where the access type is not its own
10021 -- ancestor, since saying simply "access type" would be
10024 elsif Is_Generic_Type
(Root_Type
(Btyp
)) then
10025 if Root_Type
(Btyp
) = Btyp
then
10027 ("access type must not be a generic formal type",
10031 ("ancestor access type must not be a generic " &
10038 -- If this is a renaming, an inherited operation, or a
10039 -- subprogram instance, use the original entity. This may make
10040 -- the node type-inconsistent, so this transformation can only
10041 -- be done if the node will not be reanalyzed. In particular,
10042 -- if it is within a default expression, the transformation
10043 -- must be delayed until the default subprogram is created for
10044 -- it, when the enclosing subprogram is frozen.
10046 if Is_Entity_Name
(P
)
10047 and then Is_Overloadable
(Entity
(P
))
10048 and then Present
(Alias
(Entity
(P
)))
10049 and then Expander_Active
10052 New_Occurrence_Of
(Alias
(Entity
(P
)), Sloc
(P
)));
10055 elsif Nkind
(P
) = N_Selected_Component
10056 and then Is_Overloadable
(Entity
(Selector_Name
(P
)))
10058 -- Protected operation. If operation is overloaded, must
10059 -- disambiguate. Prefix that denotes protected object itself
10060 -- is resolved with its own type.
10062 if Attr_Id
= Attribute_Unchecked_Access
then
10063 Error_Msg_Name_1
:= Aname
;
10065 ("attribute% cannot be applied to protected operation", P
);
10068 Resolve
(Prefix
(P
));
10069 Generate_Reference
(Entity
(Selector_Name
(P
)), P
);
10071 -- Implement check implied by 3.10.2 (18.1/2) : F.all'access is
10072 -- statically illegal if F is an anonymous access to subprogram.
10074 elsif Nkind
(P
) = N_Explicit_Dereference
10075 and then Is_Entity_Name
(Prefix
(P
))
10076 and then Ekind
(Etype
(Entity
(Prefix
(P
)))) =
10077 E_Anonymous_Access_Subprogram_Type
10079 Error_Msg_N
("anonymous access to subprogram "
10080 & "has deeper accessibility than any master", P
);
10082 elsif Is_Overloaded
(P
) then
10084 -- Use the designated type of the context to disambiguate
10085 -- Note that this was not strictly conformant to Ada 95,
10086 -- but was the implementation adopted by most Ada 95 compilers.
10087 -- The use of the context type to resolve an Access attribute
10088 -- reference is now mandated in AI-235 for Ada 2005.
10091 Index
: Interp_Index
;
10095 Get_First_Interp
(P
, Index
, It
);
10096 while Present
(It
.Typ
) loop
10097 if Covers
(Designated_Type
(Typ
), It
.Typ
) then
10098 Resolve
(P
, It
.Typ
);
10102 Get_Next_Interp
(Index
, It
);
10109 -- X'Access is illegal if X denotes a constant and the access type
10110 -- is access-to-variable. Same for 'Unchecked_Access. The rule
10111 -- does not apply to 'Unrestricted_Access. If the reference is a
10112 -- default-initialized aggregate component for a self-referential
10113 -- type the reference is legal.
10115 if not (Ekind
(Btyp
) = E_Access_Subprogram_Type
10116 or else Ekind
(Btyp
) = E_Anonymous_Access_Subprogram_Type
10117 or else (Is_Record_Type
(Btyp
)
10119 Present
(Corresponding_Remote_Type
(Btyp
)))
10120 or else Ekind
(Btyp
) = E_Access_Protected_Subprogram_Type
10121 or else Ekind
(Btyp
)
10122 = E_Anonymous_Access_Protected_Subprogram_Type
10123 or else Is_Access_Constant
(Btyp
)
10124 or else Is_Variable
(P
)
10125 or else Attr_Id
= Attribute_Unrestricted_Access
)
10127 if Is_Entity_Name
(P
)
10128 and then Is_Type
(Entity
(P
))
10130 -- Legality of a self-reference through an access
10131 -- attribute has been verified in Analyze_Access_Attribute.
10135 elsif Comes_From_Source
(N
) then
10136 Error_Msg_F
("access-to-variable designates constant", P
);
10140 Des_Btyp
:= Designated_Type
(Btyp
);
10142 if Ada_Version
>= Ada_2005
10143 and then Is_Incomplete_Type
(Des_Btyp
)
10145 -- Ada 2005 (AI-412): If the (sub)type is a limited view of an
10146 -- imported entity, and the non-limited view is visible, make
10147 -- use of it. If it is an incomplete subtype, use the base type
10150 if From_Limited_With
(Des_Btyp
)
10151 and then Present
(Non_Limited_View
(Des_Btyp
))
10153 Des_Btyp
:= Non_Limited_View
(Des_Btyp
);
10155 elsif Ekind
(Des_Btyp
) = E_Incomplete_Subtype
then
10156 Des_Btyp
:= Etype
(Des_Btyp
);
10160 if (Attr_Id
= Attribute_Access
10162 Attr_Id
= Attribute_Unchecked_Access
)
10163 and then (Ekind
(Btyp
) = E_General_Access_Type
10164 or else Ekind
(Btyp
) = E_Anonymous_Access_Type
)
10166 -- Ada 2005 (AI-230): Check the accessibility of anonymous
10167 -- access types for stand-alone objects, record and array
10168 -- components, and return objects. For a component definition
10169 -- the level is the same of the enclosing composite type.
10171 if Ada_Version
>= Ada_2005
10172 and then (Is_Local_Anonymous_Access
(Btyp
)
10174 -- Handle cases where Btyp is the anonymous access
10175 -- type of an Ada 2012 stand-alone object.
10177 or else Nkind
(Associated_Node_For_Itype
(Btyp
)) =
10178 N_Object_Declaration
)
10180 Object_Access_Level
(P
) > Deepest_Type_Access_Level
(Btyp
)
10181 and then Attr_Id
= Attribute_Access
10183 -- In an instance, this is a runtime check, but one we know
10184 -- will fail, so generate an appropriate warning. As usual,
10185 -- this kind of warning is an error in SPARK mode.
10187 if In_Instance_Body
then
10188 Error_Msg_Warn
:= SPARK_Mode
/= On
;
10190 ("non-local pointer cannot point to local object<<", P
);
10191 Error_Msg_F
("\Program_Error [<<", P
);
10194 Make_Raise_Program_Error
(Loc
,
10195 Reason
=> PE_Accessibility_Check_Failed
));
10196 Set_Etype
(N
, Typ
);
10200 ("non-local pointer cannot point to local object", P
);
10204 if Is_Dependent_Component_Of_Mutable_Object
(P
) then
10206 ("illegal attribute for discriminant-dependent component",
10210 -- Check static matching rule of 3.10.2(27). Nominal subtype
10211 -- of the prefix must statically match the designated type.
10213 Nom_Subt
:= Etype
(P
);
10215 if Is_Constr_Subt_For_U_Nominal
(Nom_Subt
) then
10216 Nom_Subt
:= Base_Type
(Nom_Subt
);
10219 if Is_Tagged_Type
(Designated_Type
(Typ
)) then
10221 -- If the attribute is in the context of an access
10222 -- parameter, then the prefix is allowed to be of
10223 -- the class-wide type (by AI-127).
10225 if Ekind
(Typ
) = E_Anonymous_Access_Type
then
10226 if not Covers
(Designated_Type
(Typ
), Nom_Subt
)
10227 and then not Covers
(Nom_Subt
, Designated_Type
(Typ
))
10233 Desig
:= Designated_Type
(Typ
);
10235 if Is_Class_Wide_Type
(Desig
) then
10236 Desig
:= Etype
(Desig
);
10239 if Is_Anonymous_Tagged_Base
(Nom_Subt
, Desig
) then
10244 ("type of prefix: & not compatible",
10247 ("\with &, the expected designated type",
10248 P
, Designated_Type
(Typ
));
10253 elsif not Covers
(Designated_Type
(Typ
), Nom_Subt
)
10255 (not Is_Class_Wide_Type
(Designated_Type
(Typ
))
10256 and then Is_Class_Wide_Type
(Nom_Subt
))
10259 ("type of prefix: & is not covered", P
, Nom_Subt
);
10261 ("\by &, the expected designated type" &
10262 " (RM 3.10.2 (27))", P
, Designated_Type
(Typ
));
10265 if Is_Class_Wide_Type
(Designated_Type
(Typ
))
10266 and then Has_Discriminants
(Etype
(Designated_Type
(Typ
)))
10267 and then Is_Constrained
(Etype
(Designated_Type
(Typ
)))
10268 and then Designated_Type
(Typ
) /= Nom_Subt
10270 Apply_Discriminant_Check
10271 (N
, Etype
(Designated_Type
(Typ
)));
10274 -- Ada 2005 (AI-363): Require static matching when designated
10275 -- type has discriminants and a constrained partial view, since
10276 -- in general objects of such types are mutable, so we can't
10277 -- allow the access value to designate a constrained object
10278 -- (because access values must be assumed to designate mutable
10279 -- objects when designated type does not impose a constraint).
10281 elsif Subtypes_Statically_Match
(Des_Btyp
, Nom_Subt
) then
10284 elsif Has_Discriminants
(Designated_Type
(Typ
))
10285 and then not Is_Constrained
(Des_Btyp
)
10287 (Ada_Version
< Ada_2005
10289 not Object_Type_Has_Constrained_Partial_View
10290 (Typ
=> Designated_Type
(Base_Type
(Typ
)),
10291 Scop
=> Current_Scope
))
10297 ("object subtype must statically match "
10298 & "designated subtype", P
);
10300 if Is_Entity_Name
(P
)
10301 and then Is_Array_Type
(Designated_Type
(Typ
))
10304 D
: constant Node_Id
:= Declaration_Node
(Entity
(P
));
10307 ("aliased object has explicit bounds??", D
);
10309 ("\declare without bounds (and with explicit "
10310 & "initialization)??", D
);
10312 ("\for use with unconstrained access??", D
);
10317 -- Check the static accessibility rule of 3.10.2(28). Note that
10318 -- this check is not performed for the case of an anonymous
10319 -- access type, since the access attribute is always legal
10320 -- in such a context.
10322 if Attr_Id
/= Attribute_Unchecked_Access
10323 and then Ekind
(Btyp
) = E_General_Access_Type
10325 Object_Access_Level
(P
) > Deepest_Type_Access_Level
(Btyp
)
10327 Accessibility_Message
;
10332 if Ekind_In
(Btyp
, E_Access_Protected_Subprogram_Type
,
10333 E_Anonymous_Access_Protected_Subprogram_Type
)
10335 if Is_Entity_Name
(P
)
10336 and then not Is_Protected_Type
(Scope
(Entity
(P
)))
10338 Error_Msg_F
("context requires a protected subprogram", P
);
10340 -- Check accessibility of protected object against that of the
10341 -- access type, but only on user code, because the expander
10342 -- creates access references for handlers. If the context is an
10343 -- anonymous_access_to_protected, there are no accessibility
10344 -- checks either. Omit check entirely for Unrestricted_Access.
10346 elsif Object_Access_Level
(P
) > Deepest_Type_Access_Level
(Btyp
)
10347 and then Comes_From_Source
(N
)
10348 and then Ekind
(Btyp
) = E_Access_Protected_Subprogram_Type
10349 and then Attr_Id
/= Attribute_Unrestricted_Access
10351 Accessibility_Message
;
10354 -- AI05-0225: If the context is not an access to protected
10355 -- function, the prefix must be a variable, given that it may
10356 -- be used subsequently in a protected call.
10358 elsif Nkind
(P
) = N_Selected_Component
10359 and then not Is_Variable
(Prefix
(P
))
10360 and then Ekind
(Entity
(Selector_Name
(P
))) /= E_Function
10363 ("target object of access to protected procedure "
10364 & "must be variable", N
);
10366 elsif Is_Entity_Name
(P
) then
10367 Check_Internal_Protected_Use
(N
, Entity
(P
));
10370 elsif Ekind_In
(Btyp
, E_Access_Subprogram_Type
,
10371 E_Anonymous_Access_Subprogram_Type
)
10372 and then Ekind
(Etype
(N
)) = E_Access_Protected_Subprogram_Type
10374 Error_Msg_F
("context requires a non-protected subprogram", P
);
10377 -- The context cannot be a pool-specific type, but this is a
10378 -- legality rule, not a resolution rule, so it must be checked
10379 -- separately, after possibly disambiguation (see AI-245).
10381 if Ekind
(Btyp
) = E_Access_Type
10382 and then Attr_Id
/= Attribute_Unrestricted_Access
10384 Wrong_Type
(N
, Typ
);
10387 -- The context may be a constrained access type (however ill-
10388 -- advised such subtypes might be) so in order to generate a
10389 -- constraint check when needed set the type of the attribute
10390 -- reference to the base type of the context.
10392 Set_Etype
(N
, Btyp
);
10394 -- Check for incorrect atomic/volatile reference (RM C.6(12))
10396 if Attr_Id
/= Attribute_Unrestricted_Access
then
10397 if Is_Atomic_Object
(P
)
10398 and then not Is_Atomic
(Designated_Type
(Typ
))
10401 ("access to atomic object cannot yield access-to-" &
10402 "non-atomic type", P
);
10404 elsif Is_Volatile_Object
(P
)
10405 and then not Is_Volatile
(Designated_Type
(Typ
))
10408 ("access to volatile object cannot yield access-to-" &
10409 "non-volatile type", P
);
10413 -- Check for unrestricted access where expected type is a thin
10414 -- pointer to an unconstrained array.
10416 if Non_Aliased_Prefix
(N
)
10417 and then Has_Size_Clause
(Typ
)
10418 and then RM_Size
(Typ
) = System_Address_Size
10421 DT
: constant Entity_Id
:= Designated_Type
(Typ
);
10423 if Is_Array_Type
(DT
) and then not Is_Constrained
(DT
) then
10425 ("illegal use of Unrestricted_Access attribute", P
);
10427 ("\attempt to generate thin pointer to unaliased "
10433 -- Mark that address of entity is taken
10435 if Is_Entity_Name
(P
) then
10436 Set_Address_Taken
(Entity
(P
));
10439 -- Deal with possible elaboration check
10441 if Is_Entity_Name
(P
) and then Is_Subprogram
(Entity
(P
)) then
10443 Subp_Id
: constant Entity_Id
:= Entity
(P
);
10444 Scop
: constant Entity_Id
:= Scope
(Subp_Id
);
10445 Subp_Decl
: constant Node_Id
:=
10446 Unit_Declaration_Node
(Subp_Id
);
10448 Flag_Id
: Entity_Id
;
10452 -- If the access has been taken and the body of the subprogram
10453 -- has not been see yet, indirect calls must be protected with
10454 -- elaboration checks. We have the proper elaboration machinery
10455 -- for subprograms declared in packages, but within a block or
10456 -- a subprogram the body will appear in the same declarative
10457 -- part, and we must insert a check in the eventual body itself
10458 -- using the elaboration flag that we generate now. The check
10459 -- is then inserted when the body is expanded. This processing
10460 -- is not needed for a stand alone expression function because
10461 -- the internally generated spec and body are always inserted
10462 -- as a pair in the same declarative list.
10466 and then Comes_From_Source
(Subp_Id
)
10467 and then Comes_From_Source
(N
)
10468 and then In_Open_Scopes
(Scop
)
10469 and then Ekind_In
(Scop
, E_Block
, E_Procedure
, E_Function
)
10470 and then not Has_Completion
(Subp_Id
)
10471 and then No
(Elaboration_Entity
(Subp_Id
))
10472 and then Nkind
(Subp_Decl
) = N_Subprogram_Declaration
10473 and then Nkind
(Original_Node
(Subp_Decl
)) /=
10474 N_Expression_Function
10476 -- Create elaboration variable for it
10478 Flag_Id
:= Make_Temporary
(Loc
, 'E');
10479 Set_Elaboration_Entity
(Subp_Id
, Flag_Id
);
10480 Set_Is_Frozen
(Flag_Id
);
10482 -- Insert declaration for flag after subprogram
10483 -- declaration. Note that attribute reference may
10484 -- appear within a nested scope.
10486 Insert_After_And_Analyze
(Subp_Decl
,
10487 Make_Object_Declaration
(Loc
,
10488 Defining_Identifier
=> Flag_Id
,
10489 Object_Definition
=>
10490 New_Occurrence_Of
(Standard_Short_Integer
, Loc
),
10492 Make_Integer_Literal
(Loc
, Uint_0
)));
10495 -- Taking the 'Access of an expression function freezes its
10496 -- expression (RM 13.14 10.3/3). This does not apply to an
10497 -- expression function that acts as a completion because the
10498 -- generated body is immediately analyzed and the expression
10499 -- is automatically frozen.
10501 if Ekind
(Subp_Id
) = E_Function
10502 and then Nkind
(Subp_Decl
) = N_Subprogram_Declaration
10503 and then Nkind
(Original_Node
(Subp_Decl
)) =
10504 N_Expression_Function
10505 and then Present
(Corresponding_Body
(Subp_Decl
))
10506 and then not Analyzed
(Corresponding_Body
(Subp_Decl
))
10509 Handled_Statement_Sequence
10510 (Unit_Declaration_Node
10511 (Corresponding_Body
(Subp_Decl
)));
10513 if Present
(HSS
) then
10514 Stmt
:= First
(Statements
(HSS
));
10516 if Nkind
(Stmt
) = N_Simple_Return_Statement
then
10517 Freeze_Expression
(Expression
(Stmt
));
10523 end Access_Attribute
;
10529 -- Deal with resolving the type for Address attribute, overloading
10530 -- is not permitted here, since there is no context to resolve it.
10532 when Attribute_Address | Attribute_Code_Address
=>
10533 Address_Attribute
: begin
10535 -- To be safe, assume that if the address of a variable is taken,
10536 -- it may be modified via this address, so note modification.
10538 if Is_Variable
(P
) then
10539 Note_Possible_Modification
(P
, Sure
=> False);
10542 if Nkind
(P
) in N_Subexpr
10543 and then Is_Overloaded
(P
)
10545 Get_First_Interp
(P
, Index
, It
);
10546 Get_Next_Interp
(Index
, It
);
10548 if Present
(It
.Nam
) then
10549 Error_Msg_Name_1
:= Aname
;
10551 ("prefix of % attribute cannot be overloaded", P
);
10555 if not Is_Entity_Name
(P
)
10556 or else not Is_Overloadable
(Entity
(P
))
10558 if not Is_Task_Type
(Etype
(P
))
10559 or else Nkind
(P
) = N_Explicit_Dereference
10565 -- If this is the name of a derived subprogram, or that of a
10566 -- generic actual, the address is that of the original entity.
10568 if Is_Entity_Name
(P
)
10569 and then Is_Overloadable
(Entity
(P
))
10570 and then Present
(Alias
(Entity
(P
)))
10573 New_Occurrence_Of
(Alias
(Entity
(P
)), Sloc
(P
)));
10576 if Is_Entity_Name
(P
) then
10577 Set_Address_Taken
(Entity
(P
));
10580 if Nkind
(P
) = N_Slice
then
10582 -- Arr (X .. Y)'address is identical to Arr (X)'address,
10583 -- even if the array is packed and the slice itself is not
10584 -- addressable. Transform the prefix into an indexed component.
10586 -- Note that the transformation is safe only if we know that
10587 -- the slice is non-null. That is because a null slice can have
10588 -- an out of bounds index value.
10590 -- Right now, gigi blows up if given 'Address on a slice as a
10591 -- result of some incorrect freeze nodes generated by the front
10592 -- end, and this covers up that bug in one case, but the bug is
10593 -- likely still there in the cases not handled by this code ???
10595 -- It's not clear what 'Address *should* return for a null
10596 -- slice with out of bounds indexes, this might be worth an ARG
10599 -- One approach would be to do a length check unconditionally,
10600 -- and then do the transformation below unconditionally, but
10601 -- analyze with checks off, avoiding the problem of the out of
10602 -- bounds index. This approach would interpret the address of
10603 -- an out of bounds null slice as being the address where the
10604 -- array element would be if there was one, which is probably
10605 -- as reasonable an interpretation as any ???
10608 Loc
: constant Source_Ptr
:= Sloc
(P
);
10609 D
: constant Node_Id
:= Discrete_Range
(P
);
10613 if Is_Entity_Name
(D
)
10616 (Type_Low_Bound
(Entity
(D
)),
10617 Type_High_Bound
(Entity
(D
)))
10620 Make_Attribute_Reference
(Loc
,
10621 Prefix
=> (New_Occurrence_Of
(Entity
(D
), Loc
)),
10622 Attribute_Name
=> Name_First
);
10624 elsif Nkind
(D
) = N_Range
10625 and then Not_Null_Range
(Low_Bound
(D
), High_Bound
(D
))
10627 Lo
:= Low_Bound
(D
);
10633 if Present
(Lo
) then
10635 Make_Indexed_Component
(Loc
,
10636 Prefix
=> Relocate_Node
(Prefix
(P
)),
10637 Expressions
=> New_List
(Lo
)));
10639 Analyze_And_Resolve
(P
);
10643 end Address_Attribute
;
10649 -- Prefix of Body_Version attribute can be a subprogram name which
10650 -- must not be resolved, since this is not a call.
10652 when Attribute_Body_Version
=>
10659 -- Prefix of Caller attribute is an entry name which must not
10660 -- be resolved, since this is definitely not an entry call.
10662 when Attribute_Caller
=>
10669 -- Shares processing with Address attribute
10675 -- If the prefix of the Count attribute is an entry name it must not
10676 -- be resolved, since this is definitely not an entry call. However,
10677 -- if it is an element of an entry family, the index itself may
10678 -- have to be resolved because it can be a general expression.
10680 when Attribute_Count
=>
10681 if Nkind
(P
) = N_Indexed_Component
10682 and then Is_Entity_Name
(Prefix
(P
))
10685 Indx
: constant Node_Id
:= First
(Expressions
(P
));
10686 Fam
: constant Entity_Id
:= Entity
(Prefix
(P
));
10688 Resolve
(Indx
, Entry_Index_Type
(Fam
));
10689 Apply_Range_Check
(Indx
, Entry_Index_Type
(Fam
));
10697 -- Prefix of the Elaborated attribute is a subprogram name which
10698 -- must not be resolved, since this is definitely not a call. Note
10699 -- that it is a library unit, so it cannot be overloaded here.
10701 when Attribute_Elaborated
=>
10708 -- Prefix of Enabled attribute is a check name, which must be treated
10709 -- specially and not touched by Resolve.
10711 when Attribute_Enabled
=>
10718 -- Do not resolve the prefix of Loop_Entry, instead wait until the
10719 -- attribute has been expanded (see Expand_Loop_Entry_Attributes).
10720 -- The delay ensures that any generated checks or temporaries are
10721 -- inserted before the relocated prefix.
10723 when Attribute_Loop_Entry
=>
10726 --------------------
10727 -- Mechanism_Code --
10728 --------------------
10730 -- Prefix of the Mechanism_Code attribute is a function name
10731 -- which must not be resolved. Should we check for overloaded ???
10733 when Attribute_Mechanism_Code
=>
10740 -- Most processing is done in sem_dist, after determining the
10741 -- context type. Node is rewritten as a conversion to a runtime call.
10743 when Attribute_Partition_ID
=>
10744 Process_Partition_Id
(N
);
10751 when Attribute_Pool_Address
=>
10758 -- We replace the Range attribute node with a range expression whose
10759 -- bounds are the 'First and 'Last attributes applied to the same
10760 -- prefix. The reason that we do this transformation here instead of
10761 -- in the expander is that it simplifies other parts of the semantic
10762 -- analysis which assume that the Range has been replaced; thus it
10763 -- must be done even when in semantic-only mode (note that the RM
10764 -- specifically mentions this equivalence, we take care that the
10765 -- prefix is only evaluated once).
10767 when Attribute_Range
=> Range_Attribute
:
10774 if not Is_Entity_Name
(P
)
10775 or else not Is_Type
(Entity
(P
))
10780 Dims
:= Expressions
(N
);
10783 Make_Attribute_Reference
(Loc
,
10784 Prefix
=> Duplicate_Subexpr
(P
, Name_Req
=> True),
10785 Attribute_Name
=> Name_Last
,
10786 Expressions
=> Dims
);
10789 Make_Attribute_Reference
(Loc
,
10791 Attribute_Name
=> Name_First
,
10792 Expressions
=> (Dims
));
10794 -- Do not share the dimension indicator, if present. Even
10795 -- though it is a static constant, its source location
10796 -- may be modified when printing expanded code and node
10797 -- sharing will lead to chaos in Sprint.
10799 if Present
(Dims
) then
10800 Set_Expressions
(LB
,
10801 New_List
(New_Copy_Tree
(First
(Dims
))));
10804 -- If the original was marked as Must_Not_Freeze (see code
10805 -- in Sem_Ch3.Make_Index), then make sure the rewriting
10806 -- does not freeze either.
10808 if Must_Not_Freeze
(N
) then
10809 Set_Must_Not_Freeze
(HB
);
10810 Set_Must_Not_Freeze
(LB
);
10811 Set_Must_Not_Freeze
(Prefix
(HB
));
10812 Set_Must_Not_Freeze
(Prefix
(LB
));
10815 if Raises_Constraint_Error
(Prefix
(N
)) then
10817 -- Preserve Sloc of prefix in the new bounds, so that
10818 -- the posted warning can be removed if we are within
10819 -- unreachable code.
10821 Set_Sloc
(LB
, Sloc
(Prefix
(N
)));
10822 Set_Sloc
(HB
, Sloc
(Prefix
(N
)));
10825 Rewrite
(N
, Make_Range
(Loc
, LB
, HB
));
10826 Analyze_And_Resolve
(N
, Typ
);
10828 -- Ensure that the expanded range does not have side effects
10830 Force_Evaluation
(LB
);
10831 Force_Evaluation
(HB
);
10833 -- Normally after resolving attribute nodes, Eval_Attribute
10834 -- is called to do any possible static evaluation of the node.
10835 -- However, here since the Range attribute has just been
10836 -- transformed into a range expression it is no longer an
10837 -- attribute node and therefore the call needs to be avoided
10838 -- and is accomplished by simply returning from the procedure.
10841 end Range_Attribute
;
10847 -- We will only come here during the prescan of a spec expression
10848 -- containing a Result attribute. In that case the proper Etype has
10849 -- already been set, and nothing more needs to be done here.
10851 when Attribute_Result
=>
10858 -- Prefix must not be resolved in this case, since it is not a
10859 -- real entity reference. No action of any kind is require.
10861 when Attribute_UET_Address
=>
10864 ----------------------
10865 -- Unchecked_Access --
10866 ----------------------
10868 -- Processing is shared with Access
10870 -------------------------
10871 -- Unrestricted_Access --
10872 -------------------------
10874 -- Processing is shared with Access
10880 -- Resolve aggregate components in component associations
10882 when Attribute_Update
=>
10884 Aggr
: constant Node_Id
:= First
(Expressions
(N
));
10885 Typ
: constant Entity_Id
:= Etype
(Prefix
(N
));
10891 -- Set the Etype of the aggregate to that of the prefix, even
10892 -- though the aggregate may not be a proper representation of a
10893 -- value of the type (missing or duplicated associations, etc.)
10894 -- Complete resolution of the prefix. Note that in Ada 2012 it
10895 -- can be a qualified expression that is e.g. an aggregate.
10897 Set_Etype
(Aggr
, Typ
);
10898 Resolve
(Prefix
(N
), Typ
);
10900 -- For an array type, resolve expressions with the component
10901 -- type of the array, and apply constraint checks when needed.
10903 if Is_Array_Type
(Typ
) then
10904 Assoc
:= First
(Component_Associations
(Aggr
));
10905 while Present
(Assoc
) loop
10906 Expr
:= Expression
(Assoc
);
10907 Resolve
(Expr
, Component_Type
(Typ
));
10909 -- For scalar array components set Do_Range_Check when
10910 -- needed. Constraint checking on non-scalar components
10911 -- is done in Aggregate_Constraint_Checks, but only if
10912 -- full analysis is enabled. These flags are not set in
10913 -- the front-end in GnatProve mode.
10915 if Is_Scalar_Type
(Component_Type
(Typ
))
10916 and then not Is_OK_Static_Expression
(Expr
)
10918 if Is_Entity_Name
(Expr
)
10919 and then Etype
(Expr
) = Component_Type
(Typ
)
10924 Set_Do_Range_Check
(Expr
);
10928 -- The choices in the association are static constants,
10929 -- or static aggregates each of whose components belongs
10930 -- to the proper index type. However, they must also
10931 -- belong to the index subtype (s) of the prefix, which
10932 -- may be a subtype (e.g. given by a slice).
10934 -- Choices may also be identifiers with no staticness
10935 -- requirements, in which case they must resolve to the
10944 C
:= First
(Choices
(Assoc
));
10945 while Present
(C
) loop
10946 Indx
:= First_Index
(Etype
(Prefix
(N
)));
10948 if Nkind
(C
) /= N_Aggregate
then
10949 Analyze_And_Resolve
(C
, Etype
(Indx
));
10950 Apply_Constraint_Check
(C
, Etype
(Indx
));
10951 Check_Non_Static_Context
(C
);
10954 C_E
:= First
(Expressions
(C
));
10955 while Present
(C_E
) loop
10956 Analyze_And_Resolve
(C_E
, Etype
(Indx
));
10957 Apply_Constraint_Check
(C_E
, Etype
(Indx
));
10958 Check_Non_Static_Context
(C_E
);
10972 -- For a record type, use type of each component, which is
10973 -- recorded during analysis.
10976 Assoc
:= First
(Component_Associations
(Aggr
));
10977 while Present
(Assoc
) loop
10978 Comp
:= First
(Choices
(Assoc
));
10980 if Nkind
(Comp
) /= N_Others_Choice
10981 and then not Error_Posted
(Comp
)
10983 Resolve
(Expression
(Assoc
), Etype
(Entity
(Comp
)));
10995 -- Apply range check. Note that we did not do this during the
10996 -- analysis phase, since we wanted Eval_Attribute to have a
10997 -- chance at finding an illegal out of range value.
10999 when Attribute_Val
=>
11001 -- Note that we do our own Eval_Attribute call here rather than
11002 -- use the common one, because we need to do processing after
11003 -- the call, as per above comment.
11005 Eval_Attribute
(N
);
11007 -- Eval_Attribute may replace the node with a raise CE, or
11008 -- fold it to a constant. Obviously we only apply a scalar
11009 -- range check if this did not happen.
11011 if Nkind
(N
) = N_Attribute_Reference
11012 and then Attribute_Name
(N
) = Name_Val
11014 Apply_Scalar_Range_Check
(First
(Expressions
(N
)), Btyp
);
11023 -- Prefix of Version attribute can be a subprogram name which
11024 -- must not be resolved, since this is not a call.
11026 when Attribute_Version
=>
11029 ----------------------
11030 -- Other Attributes --
11031 ----------------------
11033 -- For other attributes, resolve prefix unless it is a type. If
11034 -- the attribute reference itself is a type name ('Base and 'Class)
11035 -- then this is only legal within a task or protected record.
11038 if not Is_Entity_Name
(P
) or else not Is_Type
(Entity
(P
)) then
11042 -- If the attribute reference itself is a type name ('Base,
11043 -- 'Class) then this is only legal within a task or protected
11044 -- record. What is this all about ???
11046 if Is_Entity_Name
(N
) and then Is_Type
(Entity
(N
)) then
11047 if Is_Concurrent_Type
(Entity
(N
))
11048 and then In_Open_Scopes
(Entity
(P
))
11053 ("invalid use of subtype name in expression or call", N
);
11057 -- For attributes whose argument may be a string, complete
11058 -- resolution of argument now. This avoids premature expansion
11059 -- (and the creation of transient scopes) before the attribute
11060 -- reference is resolved.
11063 when Attribute_Value
=>
11064 Resolve
(First
(Expressions
(N
)), Standard_String
);
11066 when Attribute_Wide_Value
=>
11067 Resolve
(First
(Expressions
(N
)), Standard_Wide_String
);
11069 when Attribute_Wide_Wide_Value
=>
11070 Resolve
(First
(Expressions
(N
)), Standard_Wide_Wide_String
);
11072 when others => null;
11075 -- If the prefix of the attribute is a class-wide type then it
11076 -- will be expanded into a dispatching call to a predefined
11077 -- primitive. Therefore we must check for potential violation
11078 -- of such restriction.
11080 if Is_Class_Wide_Type
(Etype
(P
)) then
11081 Check_Restriction
(No_Dispatching_Calls
, N
);
11085 -- Normally the Freezing is done by Resolve but sometimes the Prefix
11086 -- is not resolved, in which case the freezing must be done now.
11088 Freeze_Expression
(P
);
11090 -- Finally perform static evaluation on the attribute reference
11092 Analyze_Dimension
(N
);
11093 Eval_Attribute
(N
);
11094 end Resolve_Attribute
;
11096 ------------------------
11097 -- Set_Boolean_Result --
11098 ------------------------
11100 procedure Set_Boolean_Result
(N
: Node_Id
; B
: Boolean) is
11101 Loc
: constant Source_Ptr
:= Sloc
(N
);
11104 Rewrite
(N
, New_Occurrence_Of
(Standard_True
, Loc
));
11106 Rewrite
(N
, New_Occurrence_Of
(Standard_False
, Loc
));
11108 end Set_Boolean_Result
;
11110 --------------------------------
11111 -- Stream_Attribute_Available --
11112 --------------------------------
11114 function Stream_Attribute_Available
11116 Nam
: TSS_Name_Type
;
11117 Partial_View
: Node_Id
:= Empty
) return Boolean
11119 Etyp
: Entity_Id
:= Typ
;
11121 -- Start of processing for Stream_Attribute_Available
11124 -- We need some comments in this body ???
11126 if Has_Stream_Attribute_Definition
(Typ
, Nam
) then
11130 if Is_Class_Wide_Type
(Typ
) then
11131 return not Is_Limited_Type
(Typ
)
11132 or else Stream_Attribute_Available
(Etype
(Typ
), Nam
);
11135 if Nam
= TSS_Stream_Input
11136 and then Is_Abstract_Type
(Typ
)
11137 and then not Is_Class_Wide_Type
(Typ
)
11142 if not (Is_Limited_Type
(Typ
)
11143 or else (Present
(Partial_View
)
11144 and then Is_Limited_Type
(Partial_View
)))
11149 -- In Ada 2005, Input can invoke Read, and Output can invoke Write
11151 if Nam
= TSS_Stream_Input
11152 and then Ada_Version
>= Ada_2005
11153 and then Stream_Attribute_Available
(Etyp
, TSS_Stream_Read
)
11157 elsif Nam
= TSS_Stream_Output
11158 and then Ada_Version
>= Ada_2005
11159 and then Stream_Attribute_Available
(Etyp
, TSS_Stream_Write
)
11164 -- Case of Read and Write: check for attribute definition clause that
11165 -- applies to an ancestor type.
11167 while Etype
(Etyp
) /= Etyp
loop
11168 Etyp
:= Etype
(Etyp
);
11170 if Has_Stream_Attribute_Definition
(Etyp
, Nam
) then
11175 if Ada_Version
< Ada_2005
then
11177 -- In Ada 95 mode, also consider a non-visible definition
11180 Btyp
: constant Entity_Id
:= Implementation_Base_Type
(Typ
);
11183 and then Stream_Attribute_Available
11184 (Btyp
, Nam
, Partial_View
=> Typ
);
11189 end Stream_Attribute_Available
;