1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2023, 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 Accessibility
; use Accessibility
;
27 with Aspects
; use Aspects
;
28 with Atree
; use Atree
;
29 with Checks
; use Checks
;
30 with Contracts
; use Contracts
;
31 with Debug
; use Debug
;
32 with Einfo
; use Einfo
;
33 with Einfo
.Entities
; use Einfo
.Entities
;
34 with Einfo
.Utils
; use Einfo
.Utils
;
35 with Elists
; use Elists
;
36 with Errout
; use Errout
;
37 with Exp_Ch3
; use Exp_Ch3
;
38 with Exp_Disp
; use Exp_Disp
;
39 with Exp_Tss
; use Exp_Tss
;
40 with Exp_Util
; use Exp_Util
;
41 with Expander
; use Expander
;
42 with Freeze
; use Freeze
;
43 with Ghost
; use Ghost
;
45 with Lib
.Xref
; use Lib
.Xref
;
46 with Namet
; use Namet
;
47 with Nlists
; use Nlists
;
48 with Nmake
; use Nmake
;
50 with Par_SCO
; use Par_SCO
;
51 with Restrict
; use Restrict
;
52 with Rident
; use Rident
;
53 with Rtsfind
; use Rtsfind
;
55 with Sem_Aux
; use Sem_Aux
;
56 with Sem_Case
; use Sem_Case
;
57 with Sem_Cat
; use Sem_Cat
;
58 with Sem_Ch3
; use Sem_Ch3
;
59 with Sem_Ch6
; use Sem_Ch6
;
60 with Sem_Ch7
; use Sem_Ch7
;
61 with Sem_Ch8
; use Sem_Ch8
;
62 with Sem_Dim
; use Sem_Dim
;
63 with Sem_Eval
; use Sem_Eval
;
64 with Sem_Prag
; use Sem_Prag
;
65 with Sem_Res
; use Sem_Res
;
66 with Sem_Type
; use Sem_Type
;
67 with Sem_Util
; use Sem_Util
;
68 with Sem_Warn
; use Sem_Warn
;
69 with Sinfo
; use Sinfo
;
70 with Sinfo
.Nodes
; use Sinfo
.Nodes
;
71 with Sinfo
.Utils
; use Sinfo
.Utils
;
72 with Sinput
; use Sinput
;
73 with Snames
; use Snames
;
74 with Stand
; use Stand
;
75 with System
.Case_Util
; use System
.Case_Util
;
77 with Targparm
; use Targparm
;
78 with Ttypes
; use Ttypes
;
79 with Tbuild
; use Tbuild
;
80 with Urealp
; use Urealp
;
81 with Warnsw
; use Warnsw
;
83 with GNAT
.Heap_Sort_G
;
85 package body Sem_Ch13
is
87 SSU
: constant Pos
:= System_Storage_Unit
;
88 -- Convenient short hand for commonly used constant
90 -----------------------
91 -- Local Subprograms --
92 -----------------------
94 procedure Adjust_Record_For_Reverse_Bit_Order_Ada_95
(R
: Entity_Id
);
95 -- Helper routine providing the original (pre-AI95-0133) behavior for
96 -- Adjust_Record_For_Reverse_Bit_Order.
98 procedure Alignment_Check_For_Size_Change
(Typ
: Entity_Id
; Size
: Uint
);
99 -- This routine is called after setting one of the sizes of type entity
100 -- Typ to Size. The purpose is to deal with the situation of a derived
101 -- type whose inherited alignment is no longer appropriate for the new
102 -- size value. In this case, we reset the Alignment to unknown.
104 function All_Static_Choices
(L
: List_Id
) return Boolean;
105 -- Returns true if all elements of the list are OK static choices
106 -- as defined below for Is_Static_Choice. Used for case expression
107 -- alternatives and for the right operand of a membership test. An
108 -- others_choice is static if the corresponding expression is static.
109 -- The staticness of the bounds is checked separately.
111 procedure Build_Discrete_Static_Predicate
115 -- Given a predicated type Typ, where Typ is a discrete static subtype,
116 -- whose predicate expression is Expr, tests if Expr is a static predicate,
117 -- and if so, builds the predicate range list. Nam is the name of the one
118 -- argument to the predicate function. Occurrences of the type name in the
119 -- predicate expression have been replaced by identifier references to this
120 -- name, which is unique, so any identifier with Chars matching Nam must be
121 -- a reference to the type. If the predicate is non-static, this procedure
122 -- returns doing nothing. If the predicate is static, then the predicate
123 -- list is stored in Static_Discrete_Predicate (Typ), and the Expr is
124 -- rewritten as a canonicalized membership operation.
126 function Build_Export_Import_Pragma
128 Id
: Entity_Id
) return Node_Id
;
129 -- Create the corresponding pragma for aspect Export or Import denoted by
130 -- Asp. Id is the related entity subject to the aspect. Return Empty when
131 -- the expression of aspect Asp evaluates to False or is erroneous.
133 function Build_Predicate_Function_Declaration
134 (Typ
: Entity_Id
) return Node_Id
;
135 -- Build the declaration for a predicate function. The declaration is built
136 -- at the same time as the body but inserted before, as explained below.
138 procedure Build_Predicate_Function
(Typ
: Entity_Id
; N
: Node_Id
);
139 -- If Typ has predicates (indicated by Has_Predicates being set for Typ),
140 -- then either there are pragma Predicate entries on the rep chain for the
141 -- type (note that Predicate aspects are converted to pragma Predicate), or
142 -- there are inherited aspects from a parent type, or ancestor subtypes.
143 -- This procedure builds body for the Predicate function that tests these
144 -- predicates. N is the freeze node for the type. The spec of the function
145 -- is inserted before the freeze node, and the body of the function is
146 -- inserted after the freeze node.
148 procedure Check_Pool_Size_Clash
(Ent
: Entity_Id
; SP
, SS
: Node_Id
);
149 -- Called if both Storage_Pool and Storage_Size attribute definition
150 -- clauses (SP and SS) are present for entity Ent. Issue error message.
152 procedure Freeze_Entity_Checks
(N
: Node_Id
);
153 -- Called from Analyze_Freeze_Entity and Analyze_Generic_Freeze Entity
154 -- to generate appropriate semantic checks that are delayed until this
155 -- point (they had to be delayed this long for cases of delayed aspects,
156 -- e.g. analysis of statically predicated subtypes in choices, for which
157 -- we have to be sure the subtypes in question are frozen before checking).
159 function Get_Alignment_Value
(Expr
: Node_Id
) return Uint
;
160 -- Given the expression for an alignment value, returns the corresponding
161 -- Uint value. If the value is inappropriate, then error messages are
162 -- posted as required, and a value of No_Uint is returned.
164 function Is_Operational_Item
(N
: Node_Id
) return Boolean;
165 -- A specification for a stream attribute is allowed before the full type
166 -- is declared, as explained in AI-00137 and the corrigendum. Attributes
167 -- that do not specify a representation characteristic are operational
170 function Is_Static_Choice
(N
: Node_Id
) return Boolean;
171 -- Returns True if N represents a static choice (static subtype, or
172 -- static subtype indication, or static expression, or static range).
174 -- Note that this is a bit more inclusive than we actually need
175 -- (in particular membership tests do not allow the use of subtype
176 -- indications). But that doesn't matter, we have already checked
177 -- that the construct is legal to get this far.
179 function Is_Type_Related_Rep_Item
(N
: Node_Id
) return Boolean;
180 -- Returns True for a representation clause/pragma that specifies a
181 -- type-related representation (as opposed to operational) aspect.
183 function Is_Predicate_Static
186 Warn
: Boolean := True) return Boolean;
187 -- Given predicate expression Expr, tests if Expr is predicate-static in
188 -- the sense of the rules in (RM 3.2.4 (15-24)). Occurrences of the type
189 -- name in the predicate expression have been replaced by references to
190 -- an identifier whose Chars field is Nam. This name is unique, so any
191 -- identifier with Chars matching Nam must be a reference to the type.
192 -- Returns True if the expression is predicate-static and False otherwise,
193 -- but is not in the business of setting flags or issuing error messages.
195 -- Only scalar types can have static predicates, so False is always
196 -- returned for non-scalar types.
198 -- Note: the RM seems to suggest that string types can also have static
199 -- predicates. But that really makes little sense as very few useful
200 -- predicates can be constructed for strings. Remember that:
204 -- is not a static expression. So even though the clearly faulty RM wording
205 -- allows the following:
207 -- subtype S is String with Static_Predicate => S < "DEF"
209 -- We can't allow this, otherwise we have predicate-static applying to a
210 -- larger class than static expressions, which was never intended.
212 -- The Warn parameter is True iff this is not a recursive call. This
213 -- parameter is used to avoid generating warnings for subexpressions and
214 -- for cases where the predicate expression (as originally written by
215 -- the user, before any transformations) is a Boolean literal.
217 procedure New_Put_Image_Subprogram
221 -- Similar to New_Stream_Subprogram, but for the Put_Image attribute
223 procedure New_Stream_Subprogram
227 Nam
: TSS_Name_Type
);
228 -- Create a subprogram renaming of a given stream attribute to the
229 -- designated subprogram and then in the tagged case, provide this as a
230 -- primitive operation, or in the untagged case make an appropriate TSS
231 -- entry. This is more properly an expansion activity than just semantics,
232 -- but the presence of user-defined stream functions for limited types
233 -- is a legality check, which is why this takes place here rather than in
234 -- exp_ch13, where it was previously. Nam indicates the name of the TSS
235 -- function to be generated.
237 -- To avoid elaboration anomalies with freeze nodes, for untagged types
238 -- we generate both a subprogram declaration and a subprogram renaming
239 -- declaration, so that the attribute specification is handled as a
240 -- renaming_as_body. For tagged types, the specification is one of the
243 procedure No_Type_Rep_Item
(N
: Node_Id
);
244 -- Output message indicating that no type-related aspects can be
245 -- specified due to some property of the parent type.
247 procedure Register_Address_Clause_Check
253 -- Register a check for the address clause N. The rest of the parameters
254 -- are in keeping with the components of Address_Clause_Check_Record below.
256 procedure Validate_Aspect_Aggregate
(N
: Node_Id
);
257 -- Check legality of operations given in the Ada 2022 Aggregate aspect for
260 procedure Resolve_Aspect_Aggregate
263 -- Resolve each one of the operations specified in the specification of
266 procedure Validate_Aspect_Stable_Properties
267 (E
: Entity_Id
; N
: Node_Id
; Class_Present
: Boolean);
268 -- Check legality of functions given in the Ada 2022 Stable_Properties
269 -- (or Stable_Properties'Class) aspect.
271 procedure Validate_Storage_Model_Type_Aspect
272 (Typ
: Entity_Id
; ASN
: Node_Id
);
273 -- Check legality and completeness of the aggregate associations given in
274 -- the Storage_Model_Type aspect associated with Typ.
276 procedure Resolve_Storage_Model_Type_Argument
279 Addr_Type
: in out Entity_Id
;
281 -- Resolve argument N to be of the proper kind (when a type or constant)
282 -- or to have the proper profile (when a subprogram).
284 procedure Resolve_Aspect_Stable_Properties
285 (Typ_Or_Subp
: Entity_Id
;
287 Class_Present
: Boolean);
288 -- Resolve each one of the functions specified in the specification of
289 -- aspect Stable_Properties (or Stable_Properties'Class).
291 procedure Resolve_Iterable_Operation
296 -- If the name of a primitive operation for an Iterable aspect is
297 -- overloaded, resolve according to required signature.
303 Biased
: Boolean := True);
304 -- If Biased is True, sets Has_Biased_Representation flag for E, and
305 -- outputs a warning message at node N if Warn_On_Biased_Representation is
306 -- is True. This warning inserts the string Msg to describe the construct
309 -----------------------------------------------------------
310 -- Visibility of Discriminants in Aspect Specifications --
311 -----------------------------------------------------------
313 -- The discriminants of a type are visible when analyzing the aspect
314 -- specifications of a type declaration or protected type declaration,
315 -- but not when analyzing those of a subtype declaration. The following
316 -- routines enforce this distinction.
318 procedure Push_Type
(E
: Entity_Id
);
319 -- Push scope E and make visible the discriminants of type entity E if E
320 -- has discriminants and is not a subtype.
322 procedure Pop_Type
(E
: Entity_Id
);
323 -- Remove visibility to the discriminants of type entity E and pop the
324 -- scope stack if E has discriminants and is not a subtype.
326 ----------------------------------------------
327 -- Table for Validate_Unchecked_Conversions --
328 ----------------------------------------------
330 -- The following table collects unchecked conversions for validation.
331 -- Entries are made by Validate_Unchecked_Conversion and then the call
332 -- to Validate_Unchecked_Conversions does the actual error checking and
333 -- posting of warnings. The reason for this delayed processing is to take
334 -- advantage of back-annotations of size and alignment values performed by
337 -- Note: the reason we store a Source_Ptr value instead of a Node_Id is
338 -- that by the time Validate_Unchecked_Conversions is called, Sprint will
339 -- already have modified all Sloc values if the -gnatD option is set.
341 type UC_Entry
is record
342 Eloc
: Source_Ptr
; -- node used for posting warnings
343 Source
: Entity_Id
; -- source type for unchecked conversion
344 Target
: Entity_Id
; -- target type for unchecked conversion
345 Act_Unit
: Entity_Id
; -- actual function instantiated
348 package Unchecked_Conversions
is new Table
.Table
(
349 Table_Component_Type
=> UC_Entry
,
350 Table_Index_Type
=> Int
,
351 Table_Low_Bound
=> 1,
353 Table_Increment
=> 200,
354 Table_Name
=> "Unchecked_Conversions");
356 ----------------------------------------
357 -- Table for Validate_Address_Clauses --
358 ----------------------------------------
360 -- If an address clause has the form
362 -- for X'Address use Expr
364 -- where Expr has a value known at compile time or is of the form Y'Address
365 -- or recursively is a reference to a constant initialized with either of
366 -- these forms, and the value of Expr is not a multiple of X's alignment,
367 -- or if Y has a smaller alignment than X, then that merits a warning about
368 -- possible bad alignment. The following table collects address clauses of
369 -- this kind. We put these in a table so that they can be checked after the
370 -- back end has completed annotation of the alignments of objects, since we
371 -- can catch more cases that way.
373 type Address_Clause_Check_Record
is record
375 -- The address clause
378 -- The entity of the object subject to the address clause
381 -- The value of the address in the first case
384 -- The entity of the object being overlaid in the second case
387 -- Whether the address is offset within Y in the second case
389 Alignment_Checks_Suppressed
: Boolean;
390 -- Whether alignment checks are suppressed by an active scope suppress
391 -- setting. We need to save the value in order to be able to reuse it
392 -- after the back end has been run.
395 package Address_Clause_Checks
is new Table
.Table
(
396 Table_Component_Type
=> Address_Clause_Check_Record
,
397 Table_Index_Type
=> Int
,
398 Table_Low_Bound
=> 1,
400 Table_Increment
=> 200,
401 Table_Name
=> "Address_Clause_Checks");
403 function Alignment_Checks_Suppressed
404 (ACCR
: Address_Clause_Check_Record
) return Boolean;
405 -- Return whether the alignment check generated for the address clause
408 ---------------------------------
409 -- Alignment_Checks_Suppressed --
410 ---------------------------------
412 function Alignment_Checks_Suppressed
413 (ACCR
: Address_Clause_Check_Record
) return Boolean
416 if Checks_May_Be_Suppressed
(ACCR
.X
) then
417 return Is_Check_Suppressed
(ACCR
.X
, Alignment_Check
);
419 return ACCR
.Alignment_Checks_Suppressed
;
421 end Alignment_Checks_Suppressed
;
423 -----------------------------------------
424 -- Adjust_Record_For_Reverse_Bit_Order --
425 -----------------------------------------
427 procedure Adjust_Record_For_Reverse_Bit_Order
(R
: Entity_Id
) is
428 Max_Machine_Scalar_Size
: constant Uint
:=
429 UI_From_Int
(if Reverse_Bit_Order_Threshold
>= 0
430 then Reverse_Bit_Order_Threshold
431 else System_Max_Integer_Size
);
432 -- We use this as the maximum machine scalar size
434 SSU
: constant Uint
:= UI_From_Int
(System_Storage_Unit
);
441 -- The processing done here used to depend on the Ada version, but the
442 -- behavior has been changed by AI95-0133. However this AI is a Binding
443 -- Interpretation, so we now implement it even in Ada 95 mode. But the
444 -- original behavior from unamended Ada 95 is available for the sake of
445 -- compatibility under the debugging switch -gnatd.p in Ada 95 mode.
447 if Ada_Version
< Ada_2005
and then Debug_Flag_Dot_P
then
448 Adjust_Record_For_Reverse_Bit_Order_Ada_95
(R
);
452 -- For Ada 2005, we do machine scalar processing, as fully described In
453 -- AI-133. This involves gathering all components which start at the
454 -- same byte offset and processing them together. Same approach is still
455 -- valid in later versions including Ada 2012.
457 -- Note that component clauses found on record types may be inherited,
458 -- in which case the layout of the component with such a clause still
459 -- has to be done at this point. Therefore, the processing done here
460 -- must exclusively rely on the Component_Clause of the component.
462 -- This first loop through components does two things. First it deals
463 -- with the case of components with component clauses whose length is
464 -- greater than the maximum machine scalar size (either accepting them
465 -- or rejecting as needed). Second, it counts the number of components
466 -- with component clauses whose length does not exceed this maximum for
470 Comp
:= First_Component_Or_Discriminant
(R
);
471 while Present
(Comp
) loop
472 CC
:= Component_Clause
(Comp
);
476 Fbit
: constant Uint
:= Static_Integer
(First_Bit
(CC
));
477 Lbit
: constant Uint
:= Static_Integer
(Last_Bit
(CC
));
480 -- Case of component with last bit >= max machine scalar
482 if Lbit
>= Max_Machine_Scalar_Size
then
484 -- This is allowed only if first bit is zero, and last bit
485 -- + 1 is a multiple of storage unit size.
487 if Fbit
= 0 and then (Lbit
+ 1) mod SSU
= 0 then
489 -- This is the case to give a warning if enabled
491 if Warn_On_Reverse_Bit_Order
then
493 ("info: multi-byte field specified with "
494 & "non-standard Bit_Order?.v?", CC
);
496 if Bytes_Big_Endian
then
498 ("\bytes are not reversed "
499 & "(component is big-endian)?.v?", CC
);
502 ("\bytes are not reversed "
503 & "(component is little-endian)?.v?", CC
);
507 -- Give error message for RM 13.5.1(10) violation
511 ("machine scalar rules not followed for&",
512 First_Bit
(CC
), Comp
);
514 Error_Msg_Uint_1
:= Lbit
+ 1;
515 Error_Msg_Uint_2
:= Max_Machine_Scalar_Size
;
517 ("\last bit + 1 (^) exceeds maximum machine scalar "
518 & "size (^)", First_Bit
(CC
));
520 if (Lbit
+ 1) mod SSU
/= 0 then
521 Error_Msg_Uint_1
:= SSU
;
523 ("\and is not a multiple of Storage_Unit (^) "
524 & "(RM 13.5.1(10))", First_Bit
(CC
));
527 Error_Msg_Uint_1
:= Fbit
;
529 ("\and first bit (^) is non-zero "
530 & "(RM 13.4.1(10))", First_Bit
(CC
));
534 -- OK case of machine scalar related component clause. For now,
538 Num_CC
:= Num_CC
+ 1;
543 Next_Component_Or_Discriminant
(Comp
);
546 -- We need to sort the component clauses on the basis of the Position
547 -- values in the clause, so we can group clauses with the same Position
548 -- together to determine the relevant machine scalar size.
551 Comps
: array (0 .. Num_CC
) of Entity_Id
;
552 -- Array to collect component and discriminant entities. The data
553 -- starts at index 1, the 0'th entry is for the sort routine.
555 function CP_Lt
(Op1
, Op2
: Natural) return Boolean;
556 -- Compare routine for Sort
558 procedure CP_Move
(From
: Natural; To
: Natural);
559 -- Move routine for Sort
561 package Sorting
is new GNAT
.Heap_Sort_G
(CP_Move
, CP_Lt
);
564 -- Maximum last bit value of any component in this set
567 -- Corresponding machine scalar size
571 -- Start and stop positions in the component list of the set of
572 -- components with the same starting position (that constitute
573 -- components in a single machine scalar).
579 function CP_Lt
(Op1
, Op2
: Natural) return Boolean is
582 Position
(Component_Clause
(Comps
(Op1
))) <
583 Position
(Component_Clause
(Comps
(Op2
)));
590 procedure CP_Move
(From
: Natural; To
: Natural) is
592 Comps
(To
) := Comps
(From
);
595 -- Start of processing for Sort_CC
598 -- Collect the machine scalar relevant component clauses
601 Comp
:= First_Component_Or_Discriminant
(R
);
602 while Present
(Comp
) loop
604 CC
: constant Node_Id
:= Component_Clause
(Comp
);
607 -- Collect only component clauses whose last bit is less than
608 -- machine scalar size. Any component clause whose last bit
609 -- exceeds this value does not take part in machine scalar
610 -- layout considerations. The test for Error_Posted makes sure
611 -- we exclude component clauses for which we already posted an
615 and then not Error_Posted
(Last_Bit
(CC
))
616 and then Static_Integer
(Last_Bit
(CC
)) <
617 Max_Machine_Scalar_Size
619 Num_CC
:= Num_CC
+ 1;
620 Comps
(Num_CC
) := Comp
;
624 Next_Component_Or_Discriminant
(Comp
);
627 -- Sort by ascending position number
629 Sorting
.Sort
(Num_CC
);
631 -- We now have all the components whose size does not exceed the max
632 -- machine scalar value, sorted by starting position. In this loop we
633 -- gather groups of clauses starting at the same position, to process
634 -- them in accordance with AI-133.
637 while Stop
< Num_CC
loop
642 (Last_Bit
(Component_Clause
(Comps
(Start
))));
643 while Stop
< Num_CC
loop
645 (Position
(Component_Clause
(Comps
(Stop
+ 1)))) =
647 (Position
(Component_Clause
(Comps
(Stop
))))
655 (Component_Clause
(Comps
(Stop
)))));
661 -- Now we have a group of component clauses from Start to Stop
662 -- whose positions are identical, and MaxL is the maximum last
663 -- bit value of any of these components.
665 -- We need to determine the corresponding machine scalar size.
666 -- This loop assumes that machine scalar sizes are even, and that
667 -- each possible machine scalar has twice as many bits as the next
670 MSS
:= Max_Machine_Scalar_Size
;
672 and then (MSS
/ 2) >= SSU
673 and then (MSS
/ 2) > MaxL
678 -- Here is where we fix up the Component_Bit_Offset value to
679 -- account for the reverse bit order. Some examples of what needs
680 -- to be done for the case of a machine scalar size of 8 are:
682 -- First_Bit .. Last_Bit Component_Bit_Offset
694 -- The rule is that the first bit is obtained by subtracting the
695 -- old ending bit from machine scalar size - 1.
697 for C
in Start
.. Stop
loop
699 Comp
: constant Entity_Id
:= Comps
(C
);
700 CC
: constant Node_Id
:= Component_Clause
(Comp
);
702 FB
: constant Uint
:= Static_Integer
(First_Bit
(CC
));
703 LB
: constant Uint
:= Static_Integer
(Last_Bit
(CC
));
704 NFB
: constant Uint
:= MSS
- 1 - LB
;
705 NLB
: constant Uint
:= NFB
+ LB
- FB
;
706 Pos
: constant Uint
:= Static_Integer
(Position
(CC
));
709 -- Do not warn for the artificial clause built for the tag
710 -- in Check_Record_Representation_Clause if it is inherited.
712 if Warn_On_Reverse_Bit_Order
713 and then Chars
(Comp
) /= Name_uTag
715 Error_Msg_Uint_1
:= MSS
;
717 ("info: reverse bit order in machine scalar of "
718 & "length^?.v?", First_Bit
(CC
));
719 Error_Msg_Uint_1
:= NFB
;
720 Error_Msg_Uint_2
:= NLB
;
722 if Bytes_Big_Endian
then
724 ("\big-endian range for component & is ^ .. ^?.v?",
725 First_Bit
(CC
), Comp
);
728 ("\little-endian range for component " &
730 First_Bit
(CC
), Comp
);
734 Set_Component_Bit_Offset
(Comp
, Pos
* SSU
+ NFB
);
735 Set_Esize
(Comp
, 1 + (NLB
- NFB
));
736 Set_Normalized_First_Bit
(Comp
, NFB
mod SSU
);
737 Set_Normalized_Position
(Comp
, Pos
+ NFB
/ SSU
);
742 end Adjust_Record_For_Reverse_Bit_Order
;
744 ------------------------------------------------
745 -- Adjust_Record_For_Reverse_Bit_Order_Ada_95 --
746 ------------------------------------------------
748 procedure Adjust_Record_For_Reverse_Bit_Order_Ada_95
(R
: Entity_Id
) is
753 -- For Ada 95, we just renumber bits within a storage unit. We do the
754 -- same for Ada 83 mode, since we recognize the Bit_Order attribute in
755 -- Ada 83, and are free to add this extension.
757 Comp
:= First_Component_Or_Discriminant
(R
);
758 while Present
(Comp
) loop
759 CC
:= Component_Clause
(Comp
);
761 -- If component clause is present, then deal with the non-default
762 -- bit order case for Ada 95 mode.
764 -- We only do this processing for the base type, and in fact that
765 -- is important, since otherwise if there are record subtypes, we
766 -- could reverse the bits once for each subtype, which is wrong.
768 if Present
(CC
) and then Ekind
(R
) = E_Record_Type
then
770 CFB
: constant Uint
:= Component_Bit_Offset
(Comp
);
771 CSZ
: constant Uint
:= Esize
(Comp
);
772 CLC
: constant Node_Id
:= Component_Clause
(Comp
);
773 Pos
: constant Node_Id
:= Position
(CLC
);
774 FB
: constant Node_Id
:= First_Bit
(CLC
);
776 Storage_Unit_Offset
: constant Uint
:=
777 CFB
/ System_Storage_Unit
;
779 Start_Bit
: constant Uint
:=
780 CFB
mod System_Storage_Unit
;
783 -- Cases where field goes over storage unit boundary
785 if Start_Bit
+ CSZ
> System_Storage_Unit
then
787 -- Allow multi-byte field but generate warning
789 if Start_Bit
mod System_Storage_Unit
= 0
790 and then CSZ
mod System_Storage_Unit
= 0
793 ("info: multi-byte field specified with non-standard "
794 & "Bit_Order?.v?", CLC
);
796 if Bytes_Big_Endian
then
798 ("\bytes are not reversed "
799 & "(component is big-endian)?.v?", CLC
);
802 ("\bytes are not reversed "
803 & "(component is little-endian)?.v?", CLC
);
806 -- Do not allow non-contiguous field
810 ("attempt to specify non-contiguous field not "
813 ("\caused by non-standard Bit_Order specified in "
814 & "legacy Ada 95 mode", CLC
);
817 -- Case where field fits in one storage unit
820 -- Give warning if suspicious component clause
822 if Intval
(FB
) >= System_Storage_Unit
823 and then Warn_On_Reverse_Bit_Order
826 ("info: Bit_Order clause does not affect byte "
827 & "ordering?.v?", Pos
);
829 Intval
(Pos
) + Intval
(FB
) /
832 ("info: position normalized to ^ before bit order "
833 & "interpreted?.v?", Pos
);
836 -- Here is where we fix up the Component_Bit_Offset value
837 -- to account for the reverse bit order. Some examples of
838 -- what needs to be done are:
840 -- First_Bit .. Last_Bit Component_Bit_Offset
852 -- The rule is that the first bit is obtained by subtracting
853 -- the old ending bit from storage_unit - 1.
855 Set_Component_Bit_Offset
(Comp
,
856 (Storage_Unit_Offset
* System_Storage_Unit
) +
857 (System_Storage_Unit
- 1) -
858 (Start_Bit
+ CSZ
- 1));
860 Set_Normalized_Position
(Comp
,
861 Component_Bit_Offset
(Comp
) / System_Storage_Unit
);
863 Set_Normalized_First_Bit
(Comp
,
864 Component_Bit_Offset
(Comp
) mod System_Storage_Unit
);
869 Next_Component_Or_Discriminant
(Comp
);
871 end Adjust_Record_For_Reverse_Bit_Order_Ada_95
;
873 -------------------------------------
874 -- Alignment_Check_For_Size_Change --
875 -------------------------------------
877 procedure Alignment_Check_For_Size_Change
(Typ
: Entity_Id
; Size
: Uint
) is
879 -- If the alignment is known, and not set by a rep clause, and is
880 -- inconsistent with the size being set, then reset it to unknown,
881 -- we assume in this case that the size overrides the inherited
882 -- alignment, and that the alignment must be recomputed.
884 if Known_Alignment
(Typ
)
885 and then not Has_Alignment_Clause
(Typ
)
886 and then Present
(Size
)
887 and then Size
mod (Alignment
(Typ
) * SSU
) /= 0
889 Reinit_Alignment
(Typ
);
891 end Alignment_Check_For_Size_Change
;
893 -----------------------------------
894 -- All_Membership_Choices_Static --
895 -----------------------------------
897 function All_Membership_Choices_Static
(Expr
: Node_Id
) return Boolean is
898 pragma Assert
(Nkind
(Expr
) in N_Membership_Test
);
901 (Present
(Right_Opnd
(Expr
))
903 Present
(Alternatives
(Expr
)));
905 if Present
(Right_Opnd
(Expr
)) then
906 return Is_Static_Choice
(Right_Opnd
(Expr
));
908 return All_Static_Choices
(Alternatives
(Expr
));
910 end All_Membership_Choices_Static
;
912 ------------------------
913 -- All_Static_Choices --
914 ------------------------
916 function All_Static_Choices
(L
: List_Id
) return Boolean is
921 while Present
(N
) loop
922 if not Is_Static_Choice
(N
) then
930 end All_Static_Choices
;
932 -------------------------------------
933 -- Analyze_Aspects_At_Freeze_Point --
934 -------------------------------------
936 procedure Analyze_Aspects_At_Freeze_Point
(E
: Entity_Id
) is
937 procedure Analyze_Aspect_Default_Value
(ASN
: Node_Id
);
938 -- This routine analyzes an Aspect_Default_[Component_]Value denoted by
939 -- the aspect specification node ASN.
941 procedure Check_Aspect_Too_Late
(N
: Node_Id
);
942 -- This procedure is similar to Rep_Item_Too_Late for representation
943 -- aspects that apply to type and that do not have a corresponding
945 -- Used to check in particular that the expression associated with
946 -- aspect node N for the given type (entity) of the aspect does not
947 -- appear too late according to the rules in RM 13.1(9) and 13.1(10).
949 procedure Make_Pragma_From_Boolean_Aspect
(ASN
: Node_Id
);
950 -- Given an aspect specification node ASN whose expression is an
951 -- optional Boolean, this routines creates the corresponding pragma
952 -- at the freezing point.
954 ----------------------------------
955 -- Analyze_Aspect_Default_Value --
956 ----------------------------------
958 procedure Analyze_Aspect_Default_Value
(ASN
: Node_Id
) is
959 Ent
: constant Entity_Id
:= Entity
(ASN
);
960 Expr
: constant Node_Id
:= Expression
(ASN
);
963 Set_Has_Default_Aspect
(Base_Type
(Ent
));
965 if Is_Scalar_Type
(Ent
) then
966 Set_Default_Aspect_Value
(Base_Type
(Ent
), Expr
);
968 Set_Default_Aspect_Component_Value
(Base_Type
(Ent
), Expr
);
971 Check_Aspect_Too_Late
(ASN
);
972 end Analyze_Aspect_Default_Value
;
974 ---------------------------
975 -- Check_Aspect_Too_Late --
976 ---------------------------
978 procedure Check_Aspect_Too_Late
(N
: Node_Id
) is
979 Typ
: constant Entity_Id
:= Entity
(N
);
980 Expr
: constant Node_Id
:= Expression
(N
);
982 function Find_Type_Reference
983 (Typ
: Entity_Id
; Expr
: Node_Id
) return Boolean;
984 -- Return True if a reference to type Typ is found in the expression
987 -------------------------
988 -- Find_Type_Reference --
989 -------------------------
991 function Find_Type_Reference
992 (Typ
: Entity_Id
; Expr
: Node_Id
) return Boolean
994 function Find_Type
(N
: Node_Id
) return Traverse_Result
;
995 -- Set Found to True if N refers to Typ
1001 function Find_Type
(N
: Node_Id
) return Traverse_Result
is
1004 or else (Nkind
(N
) in N_Identifier | N_Expanded_Name
1005 and then Present
(Entity
(N
))
1006 and then Entity
(N
) = Typ
)
1014 function Search_Type_Reference
is new Traverse_Func
(Find_Type
);
1017 return Search_Type_Reference
(Expr
) = Abandon
;
1018 end Find_Type_Reference
;
1020 Parent_Type
: Entity_Id
;
1023 -- Ensure Expr is analyzed so that e.g. all types are properly
1024 -- resolved for Find_Type_Reference.
1028 -- A self-referential aspect is illegal if it forces freezing the
1029 -- entity before the corresponding aspect has been analyzed.
1031 if Find_Type_Reference
(Typ
, Expr
) then
1033 ("aspect specification causes premature freezing of&", N
, Typ
);
1036 -- For representation aspects, check for case of untagged derived
1037 -- type whose parent either has primitive operations (pre Ada 2022),
1038 -- or is a by-reference type (RM 13.1(10)).
1039 -- Strictly speaking the check also applies to Ada 2012 but it is
1040 -- really too constraining for existing code already, so relax it.
1041 -- ??? Confirming aspects should be allowed here.
1043 if Is_Representation_Aspect
(Get_Aspect_Id
(N
))
1044 and then Is_Derived_Type
(Typ
)
1045 and then not Is_Tagged_Type
(Typ
)
1047 Parent_Type
:= Etype
(Base_Type
(Typ
));
1049 if Ada_Version
<= Ada_2012
1050 and then Has_Primitive_Operations
(Parent_Type
)
1053 ("|representation aspect not permitted before Ada 2022: " &
1054 "use -gnat2022!", N
);
1056 ("\parent type & has primitive operations!", N
, Parent_Type
);
1058 elsif Is_By_Reference_Type
(Parent_Type
) then
1059 No_Type_Rep_Item
(N
);
1061 ("\parent type & is a by-reference type!", N
, Parent_Type
);
1064 end Check_Aspect_Too_Late
;
1066 -------------------------------------
1067 -- Make_Pragma_From_Boolean_Aspect --
1068 -------------------------------------
1070 procedure Make_Pragma_From_Boolean_Aspect
(ASN
: Node_Id
) is
1071 Ident
: constant Node_Id
:= Identifier
(ASN
);
1072 A_Name
: constant Name_Id
:= Chars
(Ident
);
1073 A_Id
: constant Aspect_Id
:= Get_Aspect_Id
(A_Name
);
1074 Ent
: constant Entity_Id
:= Entity
(ASN
);
1075 Expr
: constant Node_Id
:= Expression
(ASN
);
1076 Loc
: constant Source_Ptr
:= Sloc
(ASN
);
1078 procedure Check_False_Aspect_For_Derived_Type
;
1079 -- This procedure checks for the case of a false aspect for a derived
1080 -- type, which improperly tries to cancel an aspect inherited from
1083 -----------------------------------------
1084 -- Check_False_Aspect_For_Derived_Type --
1085 -----------------------------------------
1087 procedure Check_False_Aspect_For_Derived_Type
is
1091 -- We are only checking derived types
1093 if not Is_Derived_Type
(E
) then
1097 Par
:= Nearest_Ancestor
(E
);
1103 if not Is_Atomic
(Par
) then
1107 when Aspect_Atomic_Components
=>
1108 if not Has_Atomic_Components
(Par
) then
1112 when Aspect_Discard_Names
=>
1113 if not Discard_Names
(Par
) then
1118 if not Is_Packed
(Par
) then
1122 when Aspect_Unchecked_Union
=>
1123 if not Is_Unchecked_Union
(Par
) then
1127 when Aspect_Volatile
=>
1128 if not Is_Volatile
(Par
) then
1132 when Aspect_Volatile_Components
=>
1133 if not Has_Volatile_Components
(Par
) then
1137 when Aspect_Volatile_Full_Access
1138 | Aspect_Full_Access_Only
1140 if not Is_Volatile_Full_Access
(Par
) then
1148 -- Fall through means we are canceling an inherited aspect
1150 Error_Msg_Name_1
:= A_Name
;
1152 ("derived type& inherits aspect%, cannot cancel", Expr
, E
);
1153 end Check_False_Aspect_For_Derived_Type
;
1160 -- Start of processing for Make_Pragma_From_Boolean_Aspect
1163 if Present
(Expr
) and then Is_False
(Static_Boolean
(Expr
)) then
1164 Check_False_Aspect_For_Derived_Type
;
1167 -- There is no Full_Access_Only pragma so use VFA instead
1169 if A_Name
= Name_Full_Access_Only
then
1170 P_Name
:= Name_Volatile_Full_Access
;
1177 Pragma_Identifier
=>
1178 Make_Identifier
(Sloc
(Ident
), P_Name
),
1179 Pragma_Argument_Associations
=> New_List
(
1180 Make_Pragma_Argument_Association
(Sloc
(Ident
),
1181 Expression
=> New_Occurrence_Of
(Ent
, Sloc
(Ident
)))));
1183 Set_From_Aspect_Specification
(Prag
, True);
1184 Set_Corresponding_Aspect
(Prag
, ASN
);
1185 Set_Aspect_Rep_Item
(ASN
, Prag
);
1186 Set_Is_Delayed_Aspect
(Prag
);
1187 Set_Parent
(Prag
, ASN
);
1189 end Make_Pragma_From_Boolean_Aspect
;
1197 -- Start of processing for Analyze_Aspects_At_Freeze_Point
1200 -- Must be visible in current scope, but if this is a type from a nested
1201 -- package it may be frozen from an object declaration in the enclosing
1202 -- scope, so install the package declarations to complete the analysis
1203 -- of the aspects, if any. If the package itself is frozen the type will
1204 -- have been frozen as well.
1206 if not Scope_Within_Or_Same
(Current_Scope
, Scope
(E
)) then
1207 if Is_Type
(E
) and then From_Nested_Package
(E
) then
1209 Pack
: constant Entity_Id
:= Scope
(E
);
1213 Install_Visible_Declarations
(Pack
);
1214 Install_Private_Declarations
(Pack
);
1215 Analyze_Aspects_At_Freeze_Point
(E
);
1217 if Is_Private_Type
(E
)
1218 and then Present
(Full_View
(E
))
1220 Analyze_Aspects_At_Freeze_Point
(Full_View
(E
));
1223 End_Package_Scope
(Pack
);
1227 -- Aspects from other entities in different contexts are analyzed
1235 -- Look for aspect specification entries for this entity
1237 ASN
:= First_Rep_Item
(E
);
1238 while Present
(ASN
) loop
1239 if Nkind
(ASN
) = N_Aspect_Specification
then
1240 exit when Entity
(ASN
) /= E
;
1242 if Is_Delayed_Aspect
(ASN
) then
1243 A_Id
:= Get_Aspect_Id
(ASN
);
1247 -- For aspects whose expression is an optional Boolean, make
1248 -- the corresponding pragma at the freeze point.
1250 when Boolean_Aspects
1251 | Library_Unit_Aspects
1253 -- Aspects Export and Import require special handling.
1254 -- Both are by definition Boolean and may benefit from
1255 -- forward references, however their expressions are
1256 -- treated as static. In addition, the syntax of their
1257 -- corresponding pragmas requires extra "pieces" which
1258 -- may also contain forward references. To account for
1259 -- all of this, the corresponding pragma is created by
1260 -- Analyze_Aspect_Export_Import, but is not analyzed as
1261 -- the complete analysis must happen now.
1263 -- Aspect Full_Access_Only must be analyzed last so that
1264 -- aspects Volatile and Atomic, if any, are analyzed.
1266 -- Skip creation of pragma Preelaborable_Initialization
1267 -- in the case where the aspect has an expression,
1268 -- because the pragma is only needed for setting flag
1269 -- Known_To_Have_Preelab_Init, which is set by other
1270 -- means following resolution of the aspect expression.
1272 if A_Id
not in Aspect_Export
1273 | Aspect_Full_Access_Only
1275 and then (A_Id
/= Aspect_Preelaborable_Initialization
1276 or else No
(Expression
(ASN
)))
1278 Make_Pragma_From_Boolean_Aspect
(ASN
);
1281 -- Special handling for aspects that don't correspond to
1282 -- pragmas/attributes.
1284 when Aspect_Default_Value
1285 | Aspect_Default_Component_Value
1287 -- Do not inherit aspect for anonymous base type of a
1288 -- scalar or array type, because they apply to the first
1289 -- subtype of the type, and will be processed when that
1290 -- first subtype is frozen.
1292 if Is_Derived_Type
(E
)
1293 and then not Comes_From_Source
(E
)
1294 and then E
/= First_Subtype
(E
)
1298 Analyze_Aspect_Default_Value
(ASN
);
1301 -- Ditto for iterator aspects, because the corresponding
1302 -- attributes may not have been analyzed yet.
1304 when Aspect_Constant_Indexing
1305 | Aspect_Default_Iterator
1306 | Aspect_Iterator_Element
1307 | Aspect_Variable_Indexing
1309 Analyze
(Expression
(ASN
));
1311 if Etype
(Expression
(ASN
)) = Any_Type
then
1313 ("\aspect must be fully defined before & is frozen",
1317 when Aspect_Integer_Literal
1318 | Aspect_Real_Literal
1319 | Aspect_String_Literal
1321 Validate_Literal_Aspect
(E
, ASN
);
1323 when Aspect_Iterable
=>
1324 Validate_Iterable_Aspect
(E
, ASN
);
1326 when Aspect_Designated_Storage_Model
=>
1327 Analyze_And_Resolve
(Expression
(ASN
));
1329 if not Is_Entity_Name
(Expression
(ASN
))
1330 or else not Is_Object
(Entity
(Expression
(ASN
)))
1332 No
(Find_Aspect
(Etype
(Expression
(ASN
)),
1333 Aspect_Storage_Model_Type
))
1336 ("must specify name of stand-alone object of type "
1337 & "with aspect Storage_Model_Type",
1340 -- Set access type's Associated_Storage_Pool to denote
1341 -- the Storage_Model_Type object given for the aspect
1342 -- (even though that isn't actually an Ada storage pool).
1345 Set_Associated_Storage_Pool
1346 (E
, Entity
(Expression
(ASN
)));
1349 when Aspect_Storage_Model_Type
=>
1350 Validate_Storage_Model_Type_Aspect
(E
, ASN
);
1352 when Aspect_Aggregate
=>
1359 Ritem
:= Aspect_Rep_Item
(ASN
);
1361 if Present
(Ritem
) then
1367 Next_Rep_Item
(ASN
);
1370 -- Make a second pass for a Full_Access_Only entry
1372 ASN
:= First_Rep_Item
(E
);
1373 while Present
(ASN
) loop
1374 if Nkind
(ASN
) = N_Aspect_Specification
then
1375 exit when Entity
(ASN
) /= E
;
1377 if Get_Aspect_Id
(ASN
) = Aspect_Full_Access_Only
then
1378 Make_Pragma_From_Boolean_Aspect
(ASN
);
1379 Ritem
:= Aspect_Rep_Item
(ASN
);
1380 if Present
(Ritem
) then
1386 Next_Rep_Item
(ASN
);
1390 and then E
/= Base_Type
(E
)
1391 and then Is_First_Subtype
(E
)
1393 Inherit_Rep_Item_Chain
(Base_Type
(E
), E
);
1395 end Analyze_Aspects_At_Freeze_Point
;
1397 -----------------------------------
1398 -- Analyze_Aspect_Specifications --
1399 -----------------------------------
1401 procedure Analyze_Aspect_Specifications
(N
: Node_Id
; E
: Entity_Id
) is
1402 pragma Assert
(Present
(E
));
1404 procedure Decorate
(Asp
: Node_Id
; Prag
: Node_Id
);
1405 -- Establish linkages between an aspect and its corresponding pragma
1407 procedure Insert_Pragma
1409 Is_Instance
: Boolean := False);
1410 -- Subsidiary to the analysis of aspects
1412 -- Always_Terminates
1416 -- Constant_After_Elaboration
1419 -- Default_Initial_Condition
1420 -- Default_Storage_Pool
1424 -- Exceptional_Cases
1425 -- Extensions_Visible
1428 -- Initial_Condition
1430 -- Max_Entry_Queue_Depth
1431 -- Max_Entry_Queue_Length
1442 -- Secondary_Stack_Size
1443 -- Subprogram_Variant
1444 -- Volatile_Function
1446 -- Insert pragma Prag such that it mimics the placement of a source
1447 -- pragma of the same kind. Flag Is_Generic should be set when the
1448 -- context denotes a generic instance.
1450 function Relocate_Expression
(Source
: Node_Id
) return Node_Id
;
1451 -- Outside of a generic this function is equivalent to Relocate_Node.
1452 -- Inside a generic it is an identity function, because Relocate_Node
1453 -- would create a new node that is not associated with the generic
1454 -- template. This association is needed to save references to entities
1455 -- that are global to the generic (and might be not visible from where
1456 -- the generic is instantiated).
1458 -- Inside a generic the original tree is shared between aspect and
1459 -- a corresponding pragma (or an attribute definition clause). This
1460 -- parallels what is done in sem_prag.adb (see Get_Argument).
1466 procedure Decorate
(Asp
: Node_Id
; Prag
: Node_Id
) is
1468 Set_Aspect_Rep_Item
(Asp
, Prag
);
1469 Set_Corresponding_Aspect
(Prag
, Asp
);
1470 Set_From_Aspect_Specification
(Prag
);
1471 Set_Parent
(Prag
, Asp
);
1478 procedure Insert_Pragma
1480 Is_Instance
: Boolean := False)
1486 Inserted
: Boolean := False;
1489 -- When the aspect appears on an entry, package, protected unit,
1490 -- subprogram, or task unit body, insert the generated pragma at the
1491 -- top of the body declarations to emulate the behavior of a source
1494 -- package body Pack with Aspect is
1496 -- package body Pack is
1499 if Nkind
(N
) in N_Entry_Body
1505 Decls
:= Declarations
(N
);
1509 Set_Declarations
(N
, Decls
);
1512 Prepend_To
(Decls
, Prag
);
1514 -- When the aspect is associated with a [generic] package declaration
1515 -- insert the generated pragma at the top of the visible declarations
1516 -- to emulate the behavior of a source pragma.
1518 -- package Pack with Aspect is
1523 elsif Nkind
(N
) in N_Generic_Package_Declaration
1524 | N_Package_Declaration
1526 Decls
:= Visible_Declarations
(Specification
(N
));
1530 Set_Visible_Declarations
(Specification
(N
), Decls
);
1533 -- The visible declarations of a generic instance have the
1534 -- following structure:
1536 -- <renamings of generic formals>
1537 -- <renamings of internally-generated spec and body>
1538 -- <first source declaration>
1540 -- Insert the pragma before the first source declaration by
1541 -- skipping the instance "header" to ensure proper visibility of
1545 Decl
:= First
(Decls
);
1546 while Present
(Decl
) loop
1547 if Comes_From_Source
(Decl
) then
1548 Insert_Before
(Decl
, Prag
);
1556 -- The pragma is placed after the instance "header"
1558 if not Inserted
then
1559 Append_To
(Decls
, Prag
);
1562 -- Otherwise this is not a generic instance
1565 Prepend_To
(Decls
, Prag
);
1568 -- When the aspect is associated with a protected unit declaration,
1569 -- insert the generated pragma at the top of the visible declarations
1570 -- the emulate the behavior of a source pragma.
1572 -- protected [type] Prot with Aspect is
1574 -- protected [type] Prot is
1577 elsif Nkind
(N
) = N_Protected_Type_Declaration
then
1578 Def
:= Protected_Definition
(N
);
1582 Make_Protected_Definition
(Sloc
(N
),
1583 Visible_Declarations
=> New_List
,
1584 End_Label
=> Empty
);
1586 Set_Protected_Definition
(N
, Def
);
1589 Decls
:= Visible_Declarations
(Def
);
1593 Set_Visible_Declarations
(Def
, Decls
);
1596 Prepend_To
(Decls
, Prag
);
1598 -- When the aspect is associated with a task unit declaration, insert
1599 -- insert the generated pragma at the top of the visible declarations
1600 -- the emulate the behavior of a source pragma.
1602 -- task [type] Prot with Aspect is
1604 -- task [type] Prot is
1607 elsif Nkind
(N
) = N_Task_Type_Declaration
then
1608 Def
:= Task_Definition
(N
);
1612 Make_Task_Definition
(Sloc
(N
),
1613 Visible_Declarations
=> New_List
,
1614 End_Label
=> Empty
);
1616 Set_Task_Definition
(N
, Def
);
1619 Decls
:= Visible_Declarations
(Def
);
1623 Set_Visible_Declarations
(Def
, Decls
);
1626 Prepend_To
(Decls
, Prag
);
1628 -- When the context is a library unit, the pragma is added to the
1629 -- Pragmas_After list.
1631 elsif Nkind
(Parent
(N
)) = N_Compilation_Unit
then
1632 Aux
:= Aux_Decls_Node
(Parent
(N
));
1634 if No
(Pragmas_After
(Aux
)) then
1635 Set_Pragmas_After
(Aux
, New_List
);
1638 Prepend
(Prag
, Pragmas_After
(Aux
));
1640 -- Default, the pragma is inserted after the context
1643 Insert_After
(N
, Prag
);
1647 -------------------------
1648 -- Relocate_Expression --
1649 -------------------------
1651 function Relocate_Expression
(Source
: Node_Id
) return Node_Id
is
1653 if Inside_A_Generic
then
1656 return Atree
.Relocate_Node
(Source
);
1658 end Relocate_Expression
;
1663 Aitem
: Node_Id
:= Empty
;
1666 L
: constant List_Id
:= Aspect_Specifications
(N
);
1667 pragma Assert
(Present
(L
));
1669 Ins_Node
: Node_Id
:= N
;
1670 -- Insert pragmas/attribute definition clause after this node when no
1671 -- delayed analysis is required.
1673 -- Start of processing for Analyze_Aspect_Specifications
1676 -- The general processing involves building an attribute definition
1677 -- clause or a pragma node that corresponds to the aspect. Then in order
1678 -- to delay the evaluation of this aspect to the freeze point, we attach
1679 -- the corresponding pragma/attribute definition clause to the aspect
1680 -- specification node, which is then placed in the Rep Item chain. In
1681 -- this case we mark the entity by setting the flag Has_Delayed_Aspects
1682 -- and we evaluate the rep item at the freeze point. When the aspect
1683 -- doesn't have a corresponding pragma/attribute definition clause, then
1684 -- its analysis is simply delayed at the freeze point.
1686 -- Some special cases don't require delay analysis, thus the aspect is
1687 -- analyzed right now.
1689 -- Note that there is a special handling for Pre, Post, Test_Case,
1690 -- Contract_Cases, Always_Terminates, Exceptional_Cases and
1691 -- Subprogram_Variant aspects. In these cases, we do not have to worry
1692 -- about delay issues, since the pragmas themselves deal with delay of
1693 -- visibility for the expression analysis. Thus, we just insert the
1694 -- pragma after the node N.
1696 -- Loop through aspects
1698 Aspect
:= First
(L
);
1699 Aspect_Loop
: while Present
(Aspect
) loop
1700 Analyze_One_Aspect
: declare
1702 Aspect_Exit
: exception;
1703 -- This exception is used to exit aspect processing completely. It
1704 -- is used when an error is detected, and no further processing is
1705 -- required. It is also used if an earlier error has left the tree
1706 -- in a state where the aspect should not be processed.
1708 Expr
: constant Node_Id
:= Expression
(Aspect
);
1709 Id
: constant Node_Id
:= Identifier
(Aspect
);
1710 Loc
: constant Source_Ptr
:= Sloc
(Aspect
);
1711 Nam
: constant Name_Id
:= Chars
(Id
);
1712 A_Id
: constant Aspect_Id
:= Get_Aspect_Id
(Nam
);
1715 Delay_Required
: Boolean;
1716 -- Set False if delay is not required
1718 Eloc
: Source_Ptr
:= No_Location
;
1719 -- Source location of expression, modified when we split PPC's. It
1720 -- is set below when Expr is present.
1722 procedure Analyze_Aspect_Convention
;
1723 -- Perform analysis of aspect Convention
1725 procedure Analyze_Aspect_Disable_Controlled
;
1726 -- Perform analysis of aspect Disable_Controlled
1728 procedure Analyze_Aspect_Export_Import
;
1729 -- Perform analysis of aspects Export or Import
1731 procedure Analyze_Aspect_External_Link_Name
;
1732 -- Perform analysis of aspects External_Name or Link_Name
1734 procedure Analyze_Aspect_Implicit_Dereference
;
1735 -- Perform analysis of the Implicit_Dereference aspects
1737 procedure Analyze_Aspect_Relaxed_Initialization
;
1738 -- Perform analysis of aspect Relaxed_Initialization
1740 procedure Analyze_Aspect_Yield
;
1741 -- Perform analysis of aspect Yield
1743 procedure Analyze_Aspect_Static
;
1744 -- Ada 2022 (AI12-0075): Perform analysis of aspect Static
1746 procedure Check_Expr_Is_OK_Static_Expression
1748 Typ
: Entity_Id
:= Empty
);
1749 -- Check the specified expression Expr to make sure that it is a
1750 -- static expression of the given type (i.e. it will be analyzed
1751 -- and resolved using this type, which can be any valid argument
1752 -- to Resolve, e.g. Any_Integer is OK). If not, give an error
1753 -- and raise Aspect_Exit. If Typ is left Empty, then any static
1754 -- expression is allowed. Includes checking that the expression
1755 -- does not raise Constraint_Error.
1757 function Directly_Specified
1758 (Id
: Entity_Id
; A
: Aspect_Id
) return Boolean;
1759 -- Returns True if the given aspect is directly (as opposed to
1760 -- via any form of inheritance) specified for the given entity.
1762 function Make_Aitem_Pragma
1763 (Pragma_Argument_Associations
: List_Id
;
1764 Pragma_Name
: Name_Id
) return Node_Id
;
1765 -- This is a wrapper for Make_Pragma used for converting aspects
1766 -- to pragmas. It takes care of Sloc (set from Loc) and building
1767 -- the pragma identifier from the given name. In addition the
1768 -- flags Class_Present and Split_PPC are set from the aspect
1769 -- node, as well as Is_Ignored. This routine also sets the
1770 -- From_Aspect_Specification in the resulting pragma node to
1771 -- True, and sets Corresponding_Aspect to point to the aspect.
1772 -- The resulting pragma is assigned to Aitem.
1774 -------------------------------
1775 -- Analyze_Aspect_Convention --
1776 -------------------------------
1778 procedure Analyze_Aspect_Convention
is
1787 -- Obtain all interfacing aspects that apply to the related
1790 Get_Interfacing_Aspects
1791 (Iface_Asp
=> Aspect
,
1792 Conv_Asp
=> Dummy_1
,
1799 -- The related entity is subject to aspect Export or Import.
1800 -- Do not process Convention now because it must be analysed
1801 -- as part of Export or Import.
1803 if Present
(Expo
) or else Present
(Imp
) then
1806 -- Otherwise Convention appears by itself
1809 -- The aspect specifies a particular convention
1811 if Present
(Expr
) then
1812 Conv
:= New_Copy_Tree
(Expr
);
1814 -- Otherwise assume convention Ada
1817 Conv
:= Make_Identifier
(Loc
, Name_Ada
);
1821 -- pragma Convention (<Conv>, <E>);
1823 Aitem
:= Make_Aitem_Pragma
1824 (Pragma_Name
=> Name_Convention
,
1825 Pragma_Argument_Associations
=> New_List
(
1826 Make_Pragma_Argument_Association
(Loc
,
1827 Expression
=> Conv
),
1828 Make_Pragma_Argument_Association
(Loc
,
1829 Expression
=> New_Occurrence_Of
(E
, Loc
))));
1831 Decorate
(Aspect
, Aitem
);
1832 Insert_Pragma
(Aitem
);
1834 end Analyze_Aspect_Convention
;
1836 ---------------------------------------
1837 -- Analyze_Aspect_Disable_Controlled --
1838 ---------------------------------------
1840 procedure Analyze_Aspect_Disable_Controlled
is
1842 -- The aspect applies only to controlled records
1844 if not (Ekind
(E
) = E_Record_Type
1845 and then Is_Controlled_Active
(E
))
1848 ("aspect % requires controlled record type", Aspect
);
1852 -- Preanalyze the expression (if any) when the aspect resides
1853 -- in a generic unit.
1855 if Inside_A_Generic
then
1856 if Present
(Expr
) then
1857 Preanalyze_And_Resolve
(Expr
, Any_Boolean
);
1860 -- Otherwise the aspect resides in a nongeneric context
1863 -- A controlled record type loses its controlled semantics
1864 -- when the expression statically evaluates to True.
1866 if Present
(Expr
) then
1867 Analyze_And_Resolve
(Expr
, Any_Boolean
);
1869 if Is_OK_Static_Expression
(Expr
) then
1870 if Is_True
(Static_Boolean
(Expr
)) then
1871 Set_Disable_Controlled
(E
);
1874 -- Otherwise the expression is not static
1878 ("expression of aspect % must be static", Aspect
);
1881 -- Otherwise the aspect appears without an expression and
1882 -- defaults to True.
1885 Set_Disable_Controlled
(E
);
1888 end Analyze_Aspect_Disable_Controlled
;
1890 ----------------------------------
1891 -- Analyze_Aspect_Export_Import --
1892 ----------------------------------
1894 procedure Analyze_Aspect_Export_Import
is
1902 -- Obtain all interfacing aspects that apply to the related
1905 Get_Interfacing_Aspects
1906 (Iface_Asp
=> Aspect
,
1907 Conv_Asp
=> Dummy_1
,
1914 -- The related entity cannot be subject to both aspects Export
1917 if Present
(Expo
) and then Present
(Imp
) then
1919 ("incompatible interfacing aspects given for &", E
);
1920 Error_Msg_Sloc
:= Sloc
(Expo
);
1921 Error_Msg_N
("\aspect Export #", E
);
1922 Error_Msg_Sloc
:= Sloc
(Imp
);
1923 Error_Msg_N
("\aspect Import #", E
);
1926 -- A variable is most likely modified from the outside. Take
1927 -- the optimistic approach to avoid spurious errors.
1929 if Ekind
(E
) = E_Variable
then
1930 Set_Never_Set_In_Source
(E
, False);
1933 -- Resolve the expression of an Import or Export here, and
1934 -- require it to be of type Boolean and static. This is not
1935 -- quite right, because in general this should be delayed,
1936 -- but that seems tricky for these, because normally Boolean
1937 -- aspects are replaced with pragmas at the freeze point in
1938 -- Make_Pragma_From_Boolean_Aspect.
1941 or else Is_True
(Static_Boolean
(Expr
))
1943 if A_Id
= Aspect_Import
then
1944 Set_Has_Completion
(E
);
1945 Set_Is_Imported
(E
);
1947 -- An imported object cannot be explicitly initialized
1949 if Nkind
(N
) = N_Object_Declaration
1950 and then Present
(Expression
(N
))
1953 ("imported entities cannot be initialized "
1954 & "(RM B.1(24))", Expression
(N
));
1958 pragma Assert
(A_Id
= Aspect_Export
);
1959 Set_Is_Exported
(E
);
1962 -- Create the proper form of pragma Export or Import taking
1963 -- into account Conversion, External_Name, and Link_Name.
1965 Aitem
:= Build_Export_Import_Pragma
(Aspect
, E
);
1967 -- Otherwise the expression is either False or erroneous. There
1968 -- is no corresponding pragma.
1973 end Analyze_Aspect_Export_Import
;
1975 ---------------------------------------
1976 -- Analyze_Aspect_External_Link_Name --
1977 ---------------------------------------
1979 procedure Analyze_Aspect_External_Link_Name
is
1987 -- Obtain all interfacing aspects that apply to the related
1990 Get_Interfacing_Aspects
1991 (Iface_Asp
=> Aspect
,
1992 Conv_Asp
=> Dummy_1
,
1999 -- Ensure that aspect External_Name applies to aspect Export or
2002 if A_Id
= Aspect_External_Name
then
2003 if No
(Expo
) and then No
(Imp
) then
2005 ("aspect External_Name requires aspect Import or "
2006 & "Export", Aspect
);
2009 -- Otherwise ensure that aspect Link_Name applies to aspect
2010 -- Export or Import.
2013 pragma Assert
(A_Id
= Aspect_Link_Name
);
2014 if No
(Expo
) and then No
(Imp
) then
2016 ("aspect Link_Name requires aspect Import or Export",
2020 end Analyze_Aspect_External_Link_Name
;
2022 -----------------------------------------
2023 -- Analyze_Aspect_Implicit_Dereference --
2024 -----------------------------------------
2026 procedure Analyze_Aspect_Implicit_Dereference
is
2028 if not Is_Type
(E
) or else not Has_Discriminants
(E
) then
2030 ("aspect must apply to a type with discriminants", Expr
);
2032 elsif not Is_Entity_Name
(Expr
) then
2034 ("aspect must name a discriminant of current type", Expr
);
2037 -- Discriminant type be an anonymous access type or an
2038 -- anonymous access to subprogram.
2040 -- Missing synchronized types???
2043 Disc
: Entity_Id
:= First_Discriminant
(E
);
2045 while Present
(Disc
) loop
2046 if Chars
(Expr
) = Chars
(Disc
)
2047 and then Ekind
(Etype
(Disc
)) in
2048 E_Anonymous_Access_Subprogram_Type |
2049 E_Anonymous_Access_Type
2051 Set_Has_Implicit_Dereference
(E
);
2052 Set_Has_Implicit_Dereference
(Disc
);
2056 Next_Discriminant
(Disc
);
2059 -- Error if no proper access discriminant
2061 if Present
(Disc
) then
2062 -- For a type extension, check whether parent has
2063 -- a reference discriminant, to verify that use is
2066 if Is_Derived_Type
(E
)
2067 and then Has_Discriminants
(Etype
(E
))
2070 Parent_Disc
: constant Entity_Id
:=
2071 Get_Reference_Discriminant
(Etype
(E
));
2073 if Present
(Parent_Disc
)
2074 and then Corresponding_Discriminant
(Disc
) /=
2078 ("reference discriminant does not match "
2079 & "discriminant of parent type", Expr
);
2086 ("not an access discriminant of&", Expr
, E
);
2091 end Analyze_Aspect_Implicit_Dereference
;
2093 -------------------------------------------
2094 -- Analyze_Aspect_Relaxed_Initialization --
2095 -------------------------------------------
2097 procedure Analyze_Aspect_Relaxed_Initialization
is
2098 procedure Analyze_Relaxed_Parameter
2099 (Subp_Id
: Entity_Id
;
2101 Seen
: in out Elist_Id
);
2102 -- Analyze parameter that appears in the expression of the
2103 -- aspect Relaxed_Initialization.
2105 -------------------------------
2106 -- Analyze_Relaxed_Parameter --
2107 -------------------------------
2109 procedure Analyze_Relaxed_Parameter
2110 (Subp_Id
: Entity_Id
;
2112 Seen
: in out Elist_Id
)
2115 -- Set name of the aspect for error messages
2116 Error_Msg_Name_1
:= Nam
;
2118 -- The relaxed parameter is a formal parameter
2120 if Nkind
(Param
) in N_Identifier | N_Expanded_Name
then
2124 Item
: constant Entity_Id
:= Entity
(Param
);
2126 -- It must be a formal of the analyzed subprogram
2128 if Scope
(Item
) = Subp_Id
then
2130 pragma Assert
(Is_Formal
(Item
));
2132 -- It must not have scalar or access type
2134 if Is_Elementary_Type
(Etype
(Item
)) then
2135 Error_Msg_N
("illegal aspect % item", Param
);
2137 ("\item must not have elementary type", Param
);
2140 -- Detect duplicated items
2142 if Contains
(Seen
, Item
) then
2143 Error_Msg_N
("duplicate aspect % item", Param
);
2145 Append_New_Elmt
(Item
, Seen
);
2148 Error_Msg_N
("illegal aspect % item", Param
);
2152 -- The relaxed parameter is the function's Result attribute
2154 elsif Is_Attribute_Result
(Param
) then
2158 Pref
: constant Node_Id
:= Prefix
(Param
);
2162 Nkind
(Pref
) in N_Identifier | N_Expanded_Name
2164 Entity
(Pref
) = Subp_Id
2166 -- Function result must not have scalar or access
2169 if Is_Elementary_Type
(Etype
(Pref
)) then
2170 Error_Msg_N
("illegal aspect % item", Param
);
2172 ("\function result must not have elementary"
2176 -- Detect duplicated items
2178 if Contains
(Seen
, Subp_Id
) then
2179 Error_Msg_N
("duplicate aspect % item", Param
);
2181 Append_New_Elmt
(Entity
(Pref
), Seen
);
2185 Error_Msg_N
("illegal aspect % item", Param
);
2189 Error_Msg_N
("illegal aspect % item", Param
);
2191 end Analyze_Relaxed_Parameter
;
2195 Seen
: Elist_Id
:= No_Elist
;
2196 -- Items that appear in the relaxed initialization aspect
2197 -- expression of a subprogram; for detecting duplicates.
2199 Restore_Scope
: Boolean;
2200 -- Will be set to True if we need to restore the scope table
2201 -- after analyzing the aspect expression.
2203 Prev_Id
: Entity_Id
;
2205 -- Start of processing for Analyze_Aspect_Relaxed_Initialization
2208 -- Set name of the aspect for error messages
2209 Error_Msg_Name_1
:= Nam
;
2211 -- Annotation of a type; no aspect expression is allowed.
2212 -- For a private type, the aspect must be attached to the
2215 -- ??? Once the exact rule for this aspect is ready, we will
2216 -- likely reject concurrent types, etc., so let's keep the code
2217 -- for types and variable separate.
2219 if Is_First_Subtype
(E
) then
2220 Prev_Id
:= Incomplete_Or_Partial_View
(E
);
2221 if Present
(Prev_Id
) then
2223 -- Aspect may appear on the full view of an incomplete
2224 -- type because the incomplete declaration cannot have
2227 if Ekind
(Prev_Id
) = E_Incomplete_Type
then
2230 Error_Msg_N
("aspect % must apply to partial view", N
);
2233 elsif Present
(Expr
) then
2234 Error_Msg_N
("illegal aspect % expression", Expr
);
2237 -- Annotation of a variable; no aspect expression is allowed
2239 elsif Ekind
(E
) = E_Variable
then
2240 if Present
(Expr
) then
2241 Error_Msg_N
("illegal aspect % expression", Expr
);
2244 -- Annotation of a constant; no aspect expression is allowed.
2245 -- For a deferred constant, the aspect must be attached to the
2248 elsif Ekind
(E
) = E_Constant
then
2249 if Present
(Incomplete_Or_Partial_View
(E
)) then
2251 ("aspect % must apply to deferred constant", N
);
2253 elsif Present
(Expr
) then
2254 Error_Msg_N
("illegal aspect % expression", Expr
);
2257 -- Annotation of a subprogram; aspect expression is required
2259 elsif Is_Subprogram_Or_Entry
(E
)
2260 or else Is_Generic_Subprogram
(E
)
2262 if Present
(Expr
) then
2264 -- If we analyze subprogram body that acts as its own
2265 -- spec, then the subprogram itself and its formals are
2266 -- already installed; otherwise, we need to install them,
2267 -- as they must be visible when analyzing the aspect
2270 if In_Open_Scopes
(E
) then
2271 Restore_Scope
:= False;
2273 Restore_Scope
:= True;
2276 -- Only formals of the subprogram itself can appear
2277 -- in Relaxed_Initialization aspect expression, not
2278 -- formals of the enclosing generic unit. (This is
2279 -- different than in Precondition or Depends aspects,
2280 -- where both kinds of formals are allowed.)
2282 Install_Formals
(E
);
2285 -- Aspect expression is either an aggregate with list of
2286 -- parameters (and possibly the Result attribute for a
2289 if Nkind
(Expr
) = N_Aggregate
then
2291 -- Component associations in the aggregate must be a
2292 -- parameter name followed by a static boolean
2295 if Present
(Component_Associations
(Expr
)) then
2298 First
(Component_Associations
(Expr
));
2300 while Present
(Assoc
) loop
2301 if List_Length
(Choices
(Assoc
)) = 1 then
2302 Analyze_Relaxed_Parameter
2303 (E
, First
(Choices
(Assoc
)), Seen
);
2305 if Inside_A_Generic
then
2306 Preanalyze_And_Resolve
2307 (Expression
(Assoc
), Any_Boolean
);
2310 (Expression
(Assoc
), Any_Boolean
);
2313 if not Is_OK_Static_Expression
2314 (Expression
(Assoc
))
2316 Error_Msg_Name_1
:= Nam
;
2318 ("expression of aspect % " &
2319 "must be static", Aspect
);
2323 Error_Msg_Name_1
:= Nam
;
2325 ("illegal aspect % expression", Expr
);
2332 -- Expressions of the aggregate are parameter names
2334 if Present
(Expressions
(Expr
)) then
2336 Param
: Node_Id
:= First
(Expressions
(Expr
));
2339 while Present
(Param
) loop
2340 Analyze_Relaxed_Parameter
(E
, Param
, Seen
);
2346 -- Mark the aggregate expression itself as analyzed;
2347 -- its subexpressions were marked when they themselves
2350 Set_Analyzed
(Expr
);
2352 -- Otherwise, it is a single name of a subprogram
2353 -- parameter (or possibly the Result attribute for
2357 Analyze_Relaxed_Parameter
(E
, Expr
, Seen
);
2360 if Restore_Scope
then
2364 Error_Msg_N
("missing expression for aspect %", N
);
2368 Error_Msg_N
("inappropriate entity for aspect %", E
);
2370 end Analyze_Aspect_Relaxed_Initialization
;
2372 ---------------------------
2373 -- Analyze_Aspect_Static --
2374 ---------------------------
2376 procedure Analyze_Aspect_Static
is
2377 function Has_Convention_Intrinsic
(L
: List_Id
) return Boolean;
2378 -- Return True if L contains a pragma argument association
2379 -- node representing a convention Intrinsic.
2381 ------------------------------
2382 -- Has_Convention_Intrinsic --
2383 ------------------------------
2385 function Has_Convention_Intrinsic
2386 (L
: List_Id
) return Boolean
2388 Arg
: Node_Id
:= First
(L
);
2390 while Present
(Arg
) loop
2391 if Nkind
(Arg
) = N_Pragma_Argument_Association
2392 and then Chars
(Arg
) = Name_Convention
2393 and then Chars
(Expression
(Arg
)) = Name_Intrinsic
2402 end Has_Convention_Intrinsic
;
2404 Is_Imported_Intrinsic
: Boolean;
2407 if Ada_Version
< Ada_2022
then
2408 Error_Msg_Ada_2022_Feature
("aspect %", Sloc
(Aspect
));
2412 Is_Imported_Intrinsic
:= Is_Imported
(E
)
2414 Has_Convention_Intrinsic
2415 (Pragma_Argument_Associations
(Import_Pragma
(E
)));
2417 -- The aspect applies only to expression functions that
2418 -- statisfy the requirements for a static expression function
2419 -- (such as having an expression that is predicate-static) as
2420 -- well as Intrinsic imported functions as a -gnatX extension.
2422 if not Is_Expression_Function
(E
)
2424 not (All_Extensions_Allowed
and then Is_Imported_Intrinsic
)
2426 if All_Extensions_Allowed
then
2428 ("aspect % requires intrinsic or expression function",
2431 elsif Is_Imported_Intrinsic
then
2432 Error_Msg_GNAT_Extension
2433 ("aspect % on intrinsic function", Sloc
(Aspect
),
2434 Is_Core_Extension
=> True);
2438 ("aspect % requires expression function", Aspect
);
2443 -- Ada 2022 (AI12-0075): Check that the function satisfies
2444 -- several requirements of static functions as specified in
2445 -- RM 6.8(5.1-5.8). Note that some of the requirements given
2446 -- there are checked elsewhere.
2449 -- The expression of the expression function must be a
2450 -- potentially static expression (RM 2022 6.8(3.2-3.4)).
2451 -- That's checked in Sem_Ch6.Analyze_Expression_Function.
2453 -- The function must not contain any calls to itself, which
2454 -- is checked in Sem_Res.Resolve_Call.
2456 -- Each formal must be of mode in and have a static subtype
2459 Formal
: Entity_Id
:= First_Formal
(E
);
2461 while Present
(Formal
) loop
2462 if Ekind
(Formal
) /= E_In_Parameter
then
2464 ("aspect % requires formals of mode IN",
2470 if not Is_Static_Subtype
(Etype
(Formal
)) then
2472 ("aspect % requires formals with static subtypes",
2478 Next_Formal
(Formal
);
2482 -- The function's result subtype must be a static subtype
2484 if not Is_Static_Subtype
(Etype
(E
)) then
2486 ("aspect % requires function with result of "
2487 & "a static subtype",
2493 -- Check that the function does not have any applicable
2494 -- precondition or postcondition expression.
2496 for Asp
in Pre_Post_Aspects
loop
2497 if Has_Aspect
(E
, Asp
) then
2498 Error_Msg_Name_1
:= Aspect_Names
(Asp
);
2500 ("aspect % is not allowed for a static "
2501 & "expression function",
2502 Find_Aspect
(E
, Asp
));
2508 -- ??? Must check that "for result type R, if the
2509 -- function is a boundary entity for type R (see 7.3.2),
2510 -- no type invariant applies to type R; if R has a
2511 -- component type C, a similar rule applies to C."
2514 -- When the expression is present, it must be static. If it
2515 -- evaluates to True, the expression function is treated as
2516 -- a static function. Otherwise the aspect appears without
2517 -- an expression and defaults to True.
2519 if Present
(Expr
) then
2520 -- Preanalyze the expression when the aspect resides in a
2521 -- generic unit. (Is this generic-related code necessary
2522 -- for this aspect? It's modeled on what's done for aspect
2523 -- Disable_Controlled. ???)
2525 if Inside_A_Generic
then
2526 Preanalyze_And_Resolve
(Expr
, Any_Boolean
);
2528 -- Otherwise the aspect resides in a nongeneric context
2531 Analyze_And_Resolve
(Expr
, Any_Boolean
);
2533 -- Error if the boolean expression is not static
2535 if not Is_OK_Static_Expression
(Expr
) then
2537 ("expression of aspect % must be static", Aspect
);
2541 end Analyze_Aspect_Static
;
2543 --------------------------
2544 -- Analyze_Aspect_Yield --
2545 --------------------------
2547 procedure Analyze_Aspect_Yield
is
2548 Expr_Value
: Boolean := False;
2551 -- Check valid entity for 'Yield
2553 if (Is_Subprogram
(E
)
2554 or else Is_Generic_Subprogram
(E
)
2555 or else Is_Entry
(E
))
2556 and then not Within_Protected_Type
(E
)
2560 elsif Within_Protected_Type
(E
) then
2562 ("aspect% not applicable to protected operation", Id
);
2567 ("aspect% only applicable to subprogram and entry "
2568 & "declarations", Id
);
2572 -- Evaluate its static expression (if available); otherwise it
2573 -- defaults to True.
2578 -- Otherwise it must have a static boolean expression
2581 if Inside_A_Generic
then
2582 Preanalyze_And_Resolve
(Expr
, Any_Boolean
);
2584 Analyze_And_Resolve
(Expr
, Any_Boolean
);
2587 if Is_OK_Static_Expression
(Expr
) then
2588 if Is_True
(Static_Boolean
(Expr
)) then
2593 ("expression of aspect % must be static", Aspect
);
2598 Set_Has_Yield_Aspect
(E
);
2601 -- If the Yield aspect is specified for a dispatching
2602 -- subprogram that inherits the aspect, the specified
2603 -- value shall be confirming.
2606 and then Is_Dispatching_Operation
(E
)
2607 and then Present
(Overridden_Operation
(E
))
2608 and then Has_Yield_Aspect
(Overridden_Operation
(E
))
2609 /= Is_True
(Static_Boolean
(Expr
))
2611 Error_Msg_N
("specification of inherited aspect% can only " &
2612 "confirm parent value", Id
);
2614 end Analyze_Aspect_Yield
;
2616 ----------------------------------------
2617 -- Check_Expr_Is_OK_Static_Expression --
2618 ----------------------------------------
2620 procedure Check_Expr_Is_OK_Static_Expression
2622 Typ
: Entity_Id
:= Empty
)
2625 if Present
(Typ
) then
2626 Analyze_And_Resolve
(Expr
, Typ
);
2628 Analyze_And_Resolve
(Expr
);
2631 -- An expression cannot be considered static if its resolution
2632 -- failed or if it's erroneous. Stop the analysis of the
2635 if Etype
(Expr
) = Any_Type
or else Error_Posted
(Expr
) then
2638 elsif Is_OK_Static_Expression
(Expr
) then
2641 -- Finally, we have a real error
2644 Error_Msg_Name_1
:= Nam
;
2645 Flag_Non_Static_Expr
2646 ("entity for aspect% must be a static expression",
2650 end Check_Expr_Is_OK_Static_Expression
;
2652 ------------------------
2653 -- Directly_Specified --
2654 ------------------------
2656 function Directly_Specified
2657 (Id
: Entity_Id
; A
: Aspect_Id
) return Boolean
2659 Aspect_Spec
: constant Node_Id
:= Find_Aspect
(Id
, A
);
2661 return Present
(Aspect_Spec
) and then Entity
(Aspect_Spec
) = Id
;
2662 end Directly_Specified
;
2664 -----------------------
2665 -- Make_Aitem_Pragma --
2666 -----------------------
2668 function Make_Aitem_Pragma
2669 (Pragma_Argument_Associations
: List_Id
;
2670 Pragma_Name
: Name_Id
) return Node_Id
2672 Args
: List_Id
:= Pragma_Argument_Associations
;
2676 -- We should never get here if aspect was disabled
2678 pragma Assert
(not Is_Disabled
(Aspect
));
2680 -- Certain aspects allow for an optional name or expression. Do
2681 -- not generate a pragma with empty argument association list.
2683 if No
(Args
) or else No
(Expression
(First
(Args
))) then
2691 Pragma_Argument_Associations
=> Args
,
2692 Pragma_Identifier
=>
2693 Make_Identifier
(Sloc
(Id
), Pragma_Name
),
2694 Class_Present
=> Class_Present
(Aspect
),
2695 Split_PPC
=> Split_PPC
(Aspect
));
2697 -- Set additional semantic fields
2699 if Is_Ignored
(Aspect
) then
2700 Set_Is_Ignored
(Aitem
);
2701 elsif Is_Checked
(Aspect
) then
2702 Set_Is_Checked
(Aitem
);
2705 Set_Corresponding_Aspect
(Aitem
, Aspect
);
2706 Set_From_Aspect_Specification
(Aitem
);
2709 end Make_Aitem_Pragma
;
2711 -- Start of processing for Analyze_One_Aspect
2714 -- Skip aspect if already analyzed, to avoid looping in some cases
2716 if Analyzed
(Aspect
) then
2720 -- Skip looking at aspect if it is totally disabled. Just mark it
2721 -- as such for later reference in the tree. This also sets the
2722 -- Is_Ignored and Is_Checked flags appropriately.
2724 Check_Applicable_Policy
(Aspect
);
2726 if Is_Disabled
(Aspect
) then
2730 -- Set the source location of expression, used in the case of
2731 -- a failed precondition/postcondition or invariant. Note that
2732 -- the source location of the expression is not usually the best
2733 -- choice here. For example, it gets located on the last AND
2734 -- keyword in a chain of boolean expressiond AND'ed together.
2735 -- It is best to put the message on the first character of the
2736 -- assertion, which is the effect of the First_Node call here.
2738 if Present
(Expr
) then
2739 Eloc
:= Sloc
(First_Node
(Expr
));
2742 -- Check restriction No_Implementation_Aspect_Specifications
2744 if Implementation_Defined_Aspect
(A_Id
) then
2746 (No_Implementation_Aspect_Specifications
, Aspect
);
2749 -- Check restriction No_Specification_Of_Aspect
2751 Check_Restriction_No_Specification_Of_Aspect
(Aspect
);
2753 -- Mark aspect analyzed (actual analysis is delayed till later)
2755 Set_Analyzed
(Aspect
);
2756 Set_Entity
(Aspect
, E
);
2758 -- Build the reference to E that will be used in the built pragmas
2760 Ent
:= New_Occurrence_Of
(E
, Sloc
(Id
));
2762 if A_Id
in Aspect_Attach_Handler | Aspect_Interrupt_Handler
then
2764 -- Treat the specification as a reference to the protected
2765 -- operation, which might otherwise appear unreferenced and
2766 -- generate spurious warnings.
2768 Generate_Reference
(E
, Id
);
2771 -- Check for duplicate aspect. Note that the Comes_From_Source
2772 -- test allows duplicate Pre/Post's that we generate internally
2773 -- to escape being flagged here.
2775 if No_Duplicates_Allowed
(A_Id
) then
2777 while Anod
/= Aspect
loop
2778 if Comes_From_Source
(Aspect
)
2779 and then Same_Aspect
(A_Id
, Get_Aspect_Id
(Anod
))
2781 Error_Msg_Name_1
:= Nam
;
2782 Error_Msg_Sloc
:= Sloc
(Anod
);
2784 -- Case of same aspect specified twice
2786 if Class_Present
(Anod
) = Class_Present
(Aspect
) then
2787 if not Class_Present
(Anod
) then
2789 ("aspect% for & previously given#",
2793 ("aspect `%''Class` for & previously given#",
2803 -- Check some general restrictions on language defined aspects
2805 if not Implementation_Defined_Aspect
(A_Id
)
2806 or else A_Id
in Aspect_Async_Readers
2807 | Aspect_Async_Writers
2808 | Aspect_Effective_Reads
2809 | Aspect_Effective_Writes
2810 | Aspect_Preelaborable_Initialization
2812 Error_Msg_Name_1
:= Nam
;
2814 -- Not allowed for renaming declarations. Examine the original
2815 -- node because a subprogram renaming may have been rewritten
2818 if Nkind
(Original_Node
(N
)) in N_Renaming_Declaration
then
2820 ("aspect % not allowed for renaming declaration",
2824 -- Not allowed for formal type declarations in previous
2825 -- versions of the language. Allowed for them only for
2826 -- shared variable control aspects.
2828 -- Original node is used in case expansion rewrote the node -
2829 -- as is the case with generic derived types.
2831 if Nkind
(Original_Node
(N
)) = N_Formal_Type_Declaration
then
2832 if Ada_Version
< Ada_2022
then
2834 ("aspect % not allowed for formal type declaration",
2837 elsif A_Id
not in Aspect_Atomic
2839 | Aspect_Independent
2840 | Aspect_Atomic_Components
2841 | Aspect_Independent_Components
2842 | Aspect_Volatile_Components
2843 | Aspect_Async_Readers
2844 | Aspect_Async_Writers
2845 | Aspect_Effective_Reads
2846 | Aspect_Effective_Writes
2847 | Aspect_Preelaborable_Initialization
2850 ("aspect % not allowed for formal type declaration",
2856 -- Copy expression for later processing by the procedures
2857 -- Check_Aspect_At_[Freeze_Point | End_Of_Declarations]
2859 -- The expression may be a subprogram name, and can
2860 -- be an operator name that appears as a string, but
2861 -- requires its own analysis procedure (see sem_ch6).
2863 if Nkind
(Expr
) = N_Operator_Symbol
then
2864 Set_Entity
(Id
, Expr
);
2866 Set_Entity
(Id
, New_Copy_Tree
(Expr
));
2869 -- Set Delay_Required as appropriate to aspect
2871 case Aspect_Delay
(A_Id
) is
2872 when Always_Delay
=>
2873 -- For Boolean aspects, do not delay if no expression
2875 if A_Id
in Boolean_Aspects | Library_Unit_Aspects
then
2876 Delay_Required
:= Present
(Expr
);
2878 Delay_Required
:= True;
2882 Delay_Required
:= False;
2886 -- For Boolean aspects, do not delay if no expression except
2887 -- for Full_Access_Only because we need to process it after
2888 -- Volatile and Atomic, which can be independently delayed.
2890 if A_Id
in Boolean_Aspects
2891 and then A_Id
/= Aspect_Full_Access_Only
2894 Delay_Required
:= False;
2896 -- For non-Boolean aspects, if the expression has the form
2897 -- of an integer literal, then do not delay, since we know
2898 -- the value cannot change. This optimization catches most
2899 -- rep clause cases.
2901 elsif A_Id
not in Boolean_Aspects
2902 and then Present
(Expr
)
2903 and then Nkind
(Expr
) = N_Integer_Literal
2905 Delay_Required
:= False;
2907 -- For Alignment and various Size aspects, do not delay for
2908 -- an attribute reference whose prefix is Standard, for
2909 -- example Standard'Maximum_Alignment or Standard'Word_Size.
2911 elsif A_Id
in Aspect_Alignment
2912 | Aspect_Component_Size
2913 | Aspect_Object_Size
2916 and then Present
(Expr
)
2917 and then Nkind
(Expr
) = N_Attribute_Reference
2918 and then Nkind
(Prefix
(Expr
)) = N_Identifier
2919 and then Chars
(Prefix
(Expr
)) = Name_Standard
2921 Delay_Required
:= False;
2923 -- All other cases are delayed
2926 Delay_Required
:= True;
2927 Set_Has_Delayed_Rep_Aspects
(E
);
2932 and then (A_Id
= Aspect_Stable_Properties
2933 or else A_Id
= Aspect_Designated_Storage_Model
2934 or else A_Id
= Aspect_Storage_Model_Type
2935 or else A_Id
= Aspect_Aggregate
)
2936 -- ??? It seems like we should do this for all aspects, not
2937 -- just these, but that causes as-yet-undiagnosed regressions.
2940 Set_Has_Delayed_Aspects
(E
);
2941 Set_Is_Delayed_Aspect
(Aspect
);
2944 -- Check 13.1(9.2/5): A representation aspect of a subtype or type
2945 -- shall not be specified (whether by a representation item or an
2946 -- aspect_specification) before the type is completely defined
2949 if Is_Representation_Aspect
(A_Id
)
2950 and then Rep_Item_Too_Early
(E
, N
)
2955 -- Processing based on specific aspect
2958 when Aspect_Unimplemented
=>
2959 null; -- ??? temp for now
2961 -- No_Aspect should be impossible
2964 raise Program_Error
;
2966 -- Case 1: Aspects corresponding to attribute definition
2972 | Aspect_Component_Size
2973 | Aspect_Constant_Indexing
2974 | Aspect_Default_Iterator
2975 | Aspect_Dispatching_Domain
2976 | Aspect_External_Tag
2979 | Aspect_Iterator_Element
2980 | Aspect_Machine_Radix
2981 | Aspect_Object_Size
2985 | Aspect_Scalar_Storage_Order
2986 | Aspect_Simple_Storage_Pool
2989 | Aspect_Storage_Pool
2990 | Aspect_Stream_Size
2992 | Aspect_Variable_Indexing
2995 -- Indexing aspects apply only to tagged type
2997 if A_Id
in Aspect_Constant_Indexing
2998 | Aspect_Variable_Indexing
2999 and then not (Is_Type
(E
)
3000 and then Is_Tagged_Type
(E
))
3003 ("indexing aspect can only apply to a tagged type",
3008 -- For the case of aspect Address, we don't consider that we
3009 -- know the entity is never set in the source, since it is
3010 -- is likely aliasing is occurring.
3012 -- Note: one might think that the analysis of the resulting
3013 -- attribute definition clause would take care of that, but
3014 -- that's not the case since it won't be from source.
3016 if A_Id
= Aspect_Address
then
3017 Set_Never_Set_In_Source
(E
, False);
3020 -- Correctness of the profile of a stream operation is
3021 -- verified at the freeze point, but we must detect the
3022 -- illegal specification of this aspect for a subtype now,
3023 -- to prevent malformed rep_item chains.
3025 if A_Id
in Aspect_Input
3030 if not Is_First_Subtype
(E
) then
3032 ("local name must be a first subtype", Aspect
);
3035 -- If stream aspect applies to the class-wide type,
3036 -- the generated attribute definition applies to the
3037 -- class-wide type as well.
3039 elsif Class_Present
(Aspect
) then
3041 Make_Attribute_Reference
(Loc
,
3043 Attribute_Name
=> Name_Class
);
3047 -- Construct the attribute_definition_clause. The expression
3048 -- in the aspect specification is simply shared with the
3049 -- constructed attribute, because it will be fully analyzed
3050 -- when the attribute is processed.
3053 Make_Attribute_Definition_Clause
(Loc
,
3056 Expression
=> Relocate_Expression
(Expr
));
3058 -- If the address is specified, then we treat the entity as
3059 -- referenced, to avoid spurious warnings. This is analogous
3060 -- to what is done with an attribute definition clause, but
3061 -- here we don't want to generate a reference because this
3062 -- is the point of definition of the entity.
3064 if A_Id
= Aspect_Address
then
3068 -- Case 2: Aspects corresponding to pragmas
3070 -- Case 2a: Aspects corresponding to pragmas with two
3071 -- arguments, where the first argument is a local name
3072 -- referring to the entity, and the second argument is the
3073 -- aspect definition expression.
3077 when Aspect_Linker_Section
=>
3078 Aitem
:= Make_Aitem_Pragma
3079 (Pragma_Argument_Associations
=> New_List
(
3080 Make_Pragma_Argument_Association
(Loc
,
3081 Expression
=> New_Occurrence_Of
(E
, Loc
)),
3082 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3083 Expression
=> Relocate_Node
(Expr
))),
3084 Pragma_Name
=> Name_Linker_Section
);
3086 -- No need to delay the processing if the entity is already
3087 -- frozen. This should only happen for subprogram bodies.
3089 if Is_Frozen
(E
) then
3090 pragma Assert
(Nkind
(N
) = N_Subprogram_Body
);
3091 Delay_Required
:= False;
3096 -- Corresponds to pragma Implemented, construct the pragma
3098 when Aspect_Synchronization
=>
3099 Aitem
:= Make_Aitem_Pragma
3100 (Pragma_Argument_Associations
=> New_List
(
3101 Make_Pragma_Argument_Association
(Loc
,
3102 Expression
=> New_Occurrence_Of
(E
, Loc
)),
3103 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3104 Expression
=> Relocate_Node
(Expr
))),
3105 Pragma_Name
=> Name_Implemented
);
3109 when Aspect_Attach_Handler
=>
3110 Aitem
:= Make_Aitem_Pragma
3111 (Pragma_Argument_Associations
=> New_List
(
3112 Make_Pragma_Argument_Association
(Sloc
(Ent
),
3114 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3115 Expression
=> Relocate_Expression
(Expr
))),
3116 Pragma_Name
=> Name_Attach_Handler
);
3118 -- We need to insert this pragma into the tree to get proper
3119 -- processing and to look valid from a placement viewpoint.
3121 Insert_Pragma
(Aitem
);
3124 -- Dynamic_Predicate, Predicate, Static_Predicate
3126 when Aspect_Dynamic_Predicate
3127 | Aspect_Ghost_Predicate
3129 | Aspect_Static_Predicate
3131 -- These aspects apply only to subtypes
3133 if not Is_Type
(E
) then
3135 ("predicate can only be specified for a subtype",
3139 elsif Is_Incomplete_Type
(E
) then
3141 ("predicate cannot apply to incomplete view", Aspect
);
3143 elsif Is_Generic_Type
(E
) then
3145 ("predicate cannot apply to formal type", Aspect
);
3149 -- Construct the pragma (always a pragma Predicate, with
3150 -- flags recording whether it is static/dynamic). We also
3151 -- set flags recording this in the type itself.
3153 Aitem
:= Make_Aitem_Pragma
3154 (Pragma_Argument_Associations
=> New_List
(
3155 Make_Pragma_Argument_Association
(Sloc
(Ent
),
3157 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3158 Expression
=> Relocate_Expression
(Expr
))),
3159 Pragma_Name
=> Name_Predicate
);
3161 -- Mark type has predicates, and remember what kind of
3162 -- aspect lead to this predicate (we need this to access
3163 -- the right set of check policies later on).
3165 Set_Has_Predicates
(E
);
3167 if A_Id
= Aspect_Dynamic_Predicate
then
3168 Set_Has_Dynamic_Predicate_Aspect
(E
);
3170 -- If the entity has a dynamic predicate, any inherited
3171 -- static predicate becomes dynamic as well, and the
3172 -- predicate function includes the conjunction of both.
3174 Set_Has_Static_Predicate_Aspect
(E
, False);
3176 elsif A_Id
= Aspect_Static_Predicate
then
3177 Set_Has_Static_Predicate_Aspect
(E
);
3178 elsif A_Id
= Aspect_Ghost_Predicate
then
3179 Set_Has_Ghost_Predicate_Aspect
(E
);
3182 -- If the type is private, indicate that its completion
3183 -- has a freeze node, because that is the one that will
3184 -- be visible at freeze time.
3186 if Is_Private_Type
(E
) and then Present
(Full_View
(E
)) then
3187 Set_Has_Predicates
(Full_View
(E
));
3189 if A_Id
= Aspect_Dynamic_Predicate
then
3190 Set_Has_Dynamic_Predicate_Aspect
(Full_View
(E
));
3191 elsif A_Id
= Aspect_Static_Predicate
then
3192 Set_Has_Static_Predicate_Aspect
(Full_View
(E
));
3193 elsif A_Id
= Aspect_Ghost_Predicate
then
3194 Set_Has_Ghost_Predicate_Aspect
(Full_View
(E
));
3197 Set_Has_Delayed_Aspects
(Full_View
(E
));
3198 Ensure_Freeze_Node
(Full_View
(E
));
3200 -- If there is an Underlying_Full_View, also create a
3201 -- freeze node for that one.
3203 if Is_Private_Type
(Full_View
(E
)) then
3205 U_Full
: constant Entity_Id
:=
3206 Underlying_Full_View
(Full_View
(E
));
3208 if Present
(U_Full
) then
3209 Set_Has_Delayed_Aspects
(U_Full
);
3210 Ensure_Freeze_Node
(U_Full
);
3216 -- Predicate_Failure
3218 when Aspect_Predicate_Failure
=>
3220 -- This aspect applies only to subtypes
3222 if not Is_Type
(E
) then
3224 ("predicate can only be specified for a subtype",
3228 elsif Is_Incomplete_Type
(E
) then
3230 ("predicate cannot apply to incomplete view", Aspect
);
3233 elsif not Has_Predicates
(E
) then
3235 ("Predicate_Failure requires previous predicate" &
3236 " specification", Aspect
);
3239 elsif not (Directly_Specified
(E
, Aspect_Dynamic_Predicate
)
3240 or else Directly_Specified
(E
, Aspect_Predicate
)
3241 or else Directly_Specified
(E
, Aspect_Ghost_Predicate
)
3242 or else Directly_Specified
(E
, Aspect_Static_Predicate
))
3245 ("Predicate_Failure requires accompanying" &
3246 " noninherited predicate specification", Aspect
);
3250 -- Construct the pragma
3252 Aitem
:= Make_Aitem_Pragma
3253 (Pragma_Argument_Associations
=> New_List
(
3254 Make_Pragma_Argument_Association
(Sloc
(Ent
),
3256 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3257 Expression
=> Relocate_Node
(Expr
))),
3258 Pragma_Name
=> Name_Predicate_Failure
);
3260 -- Case 2b: Aspects corresponding to pragmas with two
3261 -- arguments, where the second argument is a local name
3262 -- referring to the entity, and the first argument is the
3263 -- aspect definition expression.
3267 when Aspect_Convention
=>
3268 Analyze_Aspect_Convention
;
3271 -- External_Name, Link_Name
3273 when Aspect_External_Name
3276 Analyze_Aspect_External_Link_Name
;
3279 -- CPU, Interrupt_Priority, Priority
3281 -- These three aspects can be specified for a subprogram spec
3282 -- or body, in which case we analyze the expression and export
3283 -- the value of the aspect.
3285 -- Previously, we generated an equivalent pragma for bodies
3286 -- (note that the specs cannot contain these pragmas). The
3287 -- pragma was inserted ahead of local declarations, rather than
3288 -- after the body. This leads to a certain duplication between
3289 -- the processing performed for the aspect and the pragma, but
3290 -- given the straightforward handling required it is simpler
3291 -- to duplicate than to translate the aspect in the spec into
3292 -- a pragma in the declarative part of the body.
3295 | Aspect_Interrupt_Priority
3298 -- Verify the expression is static when Static_Priorities is
3301 if not Is_OK_Static_Expression
(Expr
) then
3302 Check_Restriction
(Static_Priorities
, Expr
);
3305 if Nkind
(N
) in N_Subprogram_Body | N_Subprogram_Declaration
3307 -- Analyze the aspect expression
3309 Analyze_And_Resolve
(Expr
, Standard_Integer
);
3311 -- Interrupt_Priority aspect not allowed for main
3312 -- subprograms. RM D.1 does not forbid this explicitly,
3313 -- but RM J.15.11(6/3) does not permit pragma
3314 -- Interrupt_Priority for subprograms.
3316 if A_Id
= Aspect_Interrupt_Priority
then
3318 ("Interrupt_Priority aspect cannot apply to "
3319 & "subprogram", Expr
);
3321 -- The expression must be static
3323 elsif not Is_OK_Static_Expression
(Expr
) then
3324 Flag_Non_Static_Expr
3325 ("aspect requires static expression!", Expr
);
3327 -- Check whether this is the main subprogram. Issue a
3328 -- warning only if it is obviously not a main program
3329 -- (when it has parameters or when the subprogram is
3330 -- within a package).
3332 elsif Present
(Parameter_Specifications
3333 (Specification
(N
)))
3334 or else not Is_Compilation_Unit
(Defining_Entity
(N
))
3336 -- See RM D.1(14/3) and D.16(12/3)
3339 ("aspect applied to subprogram other than the "
3340 & "main subprogram has no effect??", Expr
);
3342 -- Otherwise check in range and export the value
3344 -- For the CPU aspect
3346 elsif A_Id
= Aspect_CPU
then
3347 if Is_In_Range
(Expr
, RTE
(RE_CPU_Range
)) then
3349 -- Value is correct so we export the value to make
3350 -- it available at execution time.
3353 (Main_Unit
, UI_To_Int
(Expr_Value
(Expr
)));
3357 ("main subprogram 'C'P'U is out of range", Expr
);
3360 -- For the Priority aspect
3362 elsif A_Id
= Aspect_Priority
then
3363 if Is_In_Range
(Expr
, RTE
(RE_Priority
)) then
3365 -- Value is correct so we export the value to make
3366 -- it available at execution time.
3369 (Main_Unit
, UI_To_Int
(Expr_Value
(Expr
)));
3371 -- Ignore pragma if Relaxed_RM_Semantics to support
3372 -- other targets/non GNAT compilers.
3374 elsif not Relaxed_RM_Semantics
then
3376 ("main subprogram priority is out of range",
3381 -- Load an arbitrary entity from System.Tasking.Stages
3382 -- or System.Tasking.Restricted.Stages (depending on
3383 -- the supported profile) to make sure that one of these
3384 -- packages is implicitly with'ed, since we need to have
3385 -- the tasking run time active for the pragma Priority to
3386 -- have any effect. Previously we with'ed the package
3387 -- System.Tasking, but this package does not trigger the
3388 -- required initialization of the run-time library.
3390 if Restricted_Profile
then
3391 Discard_Node
(RTE
(RE_Activate_Restricted_Tasks
));
3393 Discard_Node
(RTE
(RE_Activate_Tasks
));
3396 -- Handling for these aspects in subprograms is complete
3400 -- For task and protected types pass the aspect as an
3405 Make_Attribute_Definition_Clause
(Loc
,
3408 Expression
=> Relocate_Expression
(Expr
));
3411 -- Suppress/Unsuppress
3413 when Aspect_Suppress
3416 Aitem
:= Make_Aitem_Pragma
3417 (Pragma_Argument_Associations
=> New_List
(
3418 Make_Pragma_Argument_Association
(Loc
,
3419 Expression
=> Relocate_Node
(Expr
)),
3420 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3421 Expression
=> New_Occurrence_Of
(E
, Loc
))),
3422 Pragma_Name
=> Nam
);
3424 Delay_Required
:= False;
3428 when Aspect_Warnings
=>
3429 Aitem
:= Make_Aitem_Pragma
3430 (Pragma_Argument_Associations
=> New_List
(
3431 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3432 Expression
=> Relocate_Node
(Expr
)),
3433 Make_Pragma_Argument_Association
(Loc
,
3434 Expression
=> New_Occurrence_Of
(E
, Loc
))),
3435 Pragma_Name
=> Name_Warnings
);
3437 Decorate
(Aspect
, Aitem
);
3438 Insert_Pragma
(Aitem
);
3441 -- Case 2c: Aspects corresponding to pragmas with three
3444 -- Invariant aspects have a first argument that references the
3445 -- entity, a second argument that is the expression and a third
3446 -- argument that is an appropriate message.
3448 -- Invariant, Type_Invariant
3450 when Aspect_Invariant
3451 | Aspect_Type_Invariant
3453 -- Analysis of the pragma will verify placement legality:
3454 -- an invariant must apply to a private type, or appear in
3455 -- the private part of a spec and apply to a completion.
3457 Aitem
:= Make_Aitem_Pragma
3458 (Pragma_Argument_Associations
=> New_List
(
3459 Make_Pragma_Argument_Association
(Sloc
(Ent
),
3461 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3462 Expression
=> Relocate_Node
(Expr
))),
3463 Pragma_Name
=> Name_Invariant
);
3465 -- Add message unless exception messages are suppressed
3467 if not Opt
.Exception_Locations_Suppressed
then
3468 Append_To
(Pragma_Argument_Associations
(Aitem
),
3469 Make_Pragma_Argument_Association
(Eloc
,
3470 Chars
=> Name_Message
,
3472 Make_String_Literal
(Eloc
,
3473 Strval
=> "failed invariant from "
3474 & Build_Location_String
(Eloc
))));
3477 -- For Invariant case, insert immediately after the entity
3478 -- declaration. We do not have to worry about delay issues
3479 -- since the pragma processing takes care of this.
3481 Delay_Required
:= False;
3483 -- Case 2d : Aspects that correspond to a pragma with one
3488 -- Aspect Abstract_State introduces implicit declarations for
3489 -- all state abstraction entities it defines. To emulate this
3490 -- behavior, insert the pragma at the beginning of the visible
3491 -- declarations of the related package so that it is analyzed
3494 when Aspect_Abstract_State
=> Abstract_State
: declare
3495 Context
: Node_Id
:= N
;
3498 -- When aspect Abstract_State appears on a generic package,
3499 -- it is propagated to the package instance. The context in
3500 -- this case is the instance spec.
3502 if Nkind
(Context
) = N_Package_Instantiation
then
3503 Context
:= Instance_Spec
(Context
);
3506 if Nkind
(Context
) in N_Generic_Package_Declaration
3507 | N_Package_Declaration
3509 Aitem
:= Make_Aitem_Pragma
3510 (Pragma_Argument_Associations
=> New_List
(
3511 Make_Pragma_Argument_Association
(Loc
,
3512 Expression
=> Relocate_Node
(Expr
))),
3513 Pragma_Name
=> Name_Abstract_State
);
3515 Decorate
(Aspect
, Aitem
);
3519 Is_Generic_Instance
(Defining_Entity
(Context
)));
3523 ("aspect & must apply to a package declaration",
3530 -- Aspect Async_Readers is never delayed because it is
3531 -- equivalent to a source pragma which appears after the
3532 -- related object declaration.
3534 when Aspect_Async_Readers
=>
3535 Aitem
:= Make_Aitem_Pragma
3536 (Pragma_Argument_Associations
=> New_List
(
3537 Make_Pragma_Argument_Association
(Loc
,
3538 Expression
=> Relocate_Node
(Expr
))),
3539 Pragma_Name
=> Name_Async_Readers
);
3541 Decorate
(Aspect
, Aitem
);
3542 Insert_Pragma
(Aitem
);
3545 -- Aspect Async_Writers is never delayed because it is
3546 -- equivalent to a source pragma which appears after the
3547 -- related object declaration.
3549 when Aspect_Async_Writers
=>
3550 Aitem
:= Make_Aitem_Pragma
3551 (Pragma_Argument_Associations
=> New_List
(
3552 Make_Pragma_Argument_Association
(Loc
,
3553 Expression
=> Relocate_Node
(Expr
))),
3554 Pragma_Name
=> Name_Async_Writers
);
3556 Decorate
(Aspect
, Aitem
);
3557 Insert_Pragma
(Aitem
);
3560 -- Aspect Constant_After_Elaboration is never delayed because
3561 -- it is equivalent to a source pragma which appears after the
3562 -- related object declaration.
3564 when Aspect_Constant_After_Elaboration
=>
3565 Aitem
:= Make_Aitem_Pragma
3566 (Pragma_Argument_Associations
=> New_List
(
3567 Make_Pragma_Argument_Association
(Loc
,
3568 Expression
=> Relocate_Node
(Expr
))),
3570 Name_Constant_After_Elaboration
);
3572 Decorate
(Aspect
, Aitem
);
3573 Insert_Pragma
(Aitem
);
3576 -- Aspect Default_Internal_Condition is never delayed because
3577 -- it is equivalent to a source pragma which appears after the
3578 -- related private type. To deal with forward references, the
3579 -- generated pragma is stored in the rep chain of the related
3580 -- private type as types do not carry contracts. The pragma is
3581 -- wrapped inside of a procedure at the freeze point of the
3582 -- private type's full view.
3584 -- A type entity argument is appended to facilitate inheriting
3585 -- the aspect from parent types (see Build_DIC_Procedure_Body),
3586 -- though that extra argument isn't documented for the pragma.
3588 when Aspect_Default_Initial_Condition
=>
3589 Aitem
:= Make_Aitem_Pragma
3590 (Pragma_Argument_Associations
=> New_List
(
3591 Make_Pragma_Argument_Association
(Loc
,
3592 Expression
=> Relocate_Node
(Expr
)),
3593 Make_Pragma_Argument_Association
(Sloc
(Ent
),
3594 Expression
=> Ent
)),
3596 Name_Default_Initial_Condition
);
3598 Decorate
(Aspect
, Aitem
);
3599 Insert_Pragma
(Aitem
);
3602 -- Default_Storage_Pool
3604 when Aspect_Default_Storage_Pool
=>
3605 Aitem
:= Make_Aitem_Pragma
3606 (Pragma_Argument_Associations
=> New_List
(
3607 Make_Pragma_Argument_Association
(Loc
,
3608 Expression
=> Relocate_Node
(Expr
))),
3610 Name_Default_Storage_Pool
);
3612 Decorate
(Aspect
, Aitem
);
3613 Insert_Pragma
(Aitem
);
3618 -- Aspect Depends is never delayed because it is equivalent to
3619 -- a source pragma which appears after the related subprogram.
3620 -- To deal with forward references, the generated pragma is
3621 -- stored in the contract of the related subprogram and later
3622 -- analyzed at the end of the declarative region. See routine
3623 -- Analyze_Depends_In_Decl_Part for details.
3625 when Aspect_Depends
=>
3626 Aitem
:= Make_Aitem_Pragma
3627 (Pragma_Argument_Associations
=> New_List
(
3628 Make_Pragma_Argument_Association
(Loc
,
3629 Expression
=> Relocate_Node
(Expr
))),
3630 Pragma_Name
=> Name_Depends
);
3632 Decorate
(Aspect
, Aitem
);
3633 Insert_Pragma
(Aitem
);
3636 -- Aspect Effective_Reads is never delayed because it is
3637 -- equivalent to a source pragma which appears after the
3638 -- related object declaration.
3640 when Aspect_Effective_Reads
=>
3641 Aitem
:= Make_Aitem_Pragma
3642 (Pragma_Argument_Associations
=> New_List
(
3643 Make_Pragma_Argument_Association
(Loc
,
3644 Expression
=> Relocate_Node
(Expr
))),
3645 Pragma_Name
=> Name_Effective_Reads
);
3647 Decorate
(Aspect
, Aitem
);
3648 Insert_Pragma
(Aitem
);
3651 -- Aspect Effective_Writes is never delayed because it is
3652 -- equivalent to a source pragma which appears after the
3653 -- related object declaration.
3655 when Aspect_Effective_Writes
=>
3656 Aitem
:= Make_Aitem_Pragma
3657 (Pragma_Argument_Associations
=> New_List
(
3658 Make_Pragma_Argument_Association
(Loc
,
3659 Expression
=> Relocate_Node
(Expr
))),
3660 Pragma_Name
=> Name_Effective_Writes
);
3662 Decorate
(Aspect
, Aitem
);
3663 Insert_Pragma
(Aitem
);
3666 -- Aspect Extensions_Visible is never delayed because it is
3667 -- equivalent to a source pragma which appears after the
3668 -- related subprogram.
3670 when Aspect_Extensions_Visible
=>
3671 Aitem
:= Make_Aitem_Pragma
3672 (Pragma_Argument_Associations
=> New_List
(
3673 Make_Pragma_Argument_Association
(Loc
,
3674 Expression
=> Relocate_Node
(Expr
))),
3675 Pragma_Name
=> Name_Extensions_Visible
);
3677 Decorate
(Aspect
, Aitem
);
3678 Insert_Pragma
(Aitem
);
3681 -- Aspect Ghost is never delayed because it is equivalent to a
3682 -- source pragma which appears at the top of [generic] package
3683 -- declarations or after an object, a [generic] subprogram, or
3684 -- a type declaration.
3686 when Aspect_Ghost
=>
3687 Aitem
:= Make_Aitem_Pragma
3688 (Pragma_Argument_Associations
=> New_List
(
3689 Make_Pragma_Argument_Association
(Loc
,
3690 Expression
=> Relocate_Node
(Expr
))),
3691 Pragma_Name
=> Name_Ghost
);
3693 Decorate
(Aspect
, Aitem
);
3694 Insert_Pragma
(Aitem
);
3699 -- Aspect Global is never delayed because it is equivalent to
3700 -- a source pragma which appears after the related subprogram.
3701 -- To deal with forward references, the generated pragma is
3702 -- stored in the contract of the related subprogram and later
3703 -- analyzed at the end of the declarative region. See routine
3704 -- Analyze_Global_In_Decl_Part for details.
3706 when Aspect_Global
=>
3707 Aitem
:= Make_Aitem_Pragma
3708 (Pragma_Argument_Associations
=> New_List
(
3709 Make_Pragma_Argument_Association
(Loc
,
3710 Expression
=> Relocate_Node
(Expr
))),
3711 Pragma_Name
=> Name_Global
);
3713 Decorate
(Aspect
, Aitem
);
3714 Insert_Pragma
(Aitem
);
3717 -- Initial_Condition
3719 -- Aspect Initial_Condition is never delayed because it is
3720 -- equivalent to a source pragma which appears after the
3721 -- related package. To deal with forward references, the
3722 -- generated pragma is stored in the contract of the related
3723 -- package and later analyzed at the end of the declarative
3724 -- region. See routine Analyze_Initial_Condition_In_Decl_Part
3727 when Aspect_Initial_Condition
=> Initial_Condition
: declare
3728 Context
: Node_Id
:= N
;
3731 -- When aspect Initial_Condition appears on a generic
3732 -- package, it is propagated to the package instance. The
3733 -- context in this case is the instance spec.
3735 if Nkind
(Context
) = N_Package_Instantiation
then
3736 Context
:= Instance_Spec
(Context
);
3739 if Nkind
(Context
) in N_Generic_Package_Declaration
3740 | N_Package_Declaration
3742 Aitem
:= Make_Aitem_Pragma
3743 (Pragma_Argument_Associations
=> New_List
(
3744 Make_Pragma_Argument_Association
(Loc
,
3745 Expression
=> Relocate_Node
(Expr
))),
3747 Name_Initial_Condition
);
3749 Decorate
(Aspect
, Aitem
);
3753 Is_Generic_Instance
(Defining_Entity
(Context
)));
3755 -- Otherwise the context is illegal
3759 ("aspect & must apply to a package declaration",
3764 end Initial_Condition
;
3768 -- Aspect Initializes is never delayed because it is equivalent
3769 -- to a source pragma appearing after the related package. To
3770 -- deal with forward references, the generated pragma is stored
3771 -- in the contract of the related package and later analyzed at
3772 -- the end of the declarative region. For details, see routine
3773 -- Analyze_Initializes_In_Decl_Part.
3775 when Aspect_Initializes
=> Initializes
: declare
3776 Context
: Node_Id
:= N
;
3779 -- When aspect Initializes appears on a generic package,
3780 -- it is propagated to the package instance. The context
3781 -- in this case is the instance spec.
3783 if Nkind
(Context
) = N_Package_Instantiation
then
3784 Context
:= Instance_Spec
(Context
);
3787 if Nkind
(Context
) in N_Generic_Package_Declaration
3788 | N_Package_Declaration
3790 Aitem
:= Make_Aitem_Pragma
3791 (Pragma_Argument_Associations
=> New_List
(
3792 Make_Pragma_Argument_Association
(Loc
,
3793 Expression
=> Relocate_Node
(Expr
))),
3794 Pragma_Name
=> Name_Initializes
);
3796 Decorate
(Aspect
, Aitem
);
3800 Is_Generic_Instance
(Defining_Entity
(Context
)));
3802 -- Otherwise the context is illegal
3806 ("aspect & must apply to a package declaration",
3813 -- Max_Entry_Queue_Depth
3815 when Aspect_Max_Entry_Queue_Depth
=>
3816 Aitem
:= Make_Aitem_Pragma
3817 (Pragma_Argument_Associations
=> New_List
(
3818 Make_Pragma_Argument_Association
(Loc
,
3819 Expression
=> Relocate_Node
(Expr
))),
3820 Pragma_Name
=> Name_Max_Entry_Queue_Depth
);
3822 Decorate
(Aspect
, Aitem
);
3823 Insert_Pragma
(Aitem
);
3826 -- Max_Entry_Queue_Length
3828 when Aspect_Max_Entry_Queue_Length
=>
3829 Aitem
:= Make_Aitem_Pragma
3830 (Pragma_Argument_Associations
=> New_List
(
3831 Make_Pragma_Argument_Association
(Loc
,
3832 Expression
=> Relocate_Node
(Expr
))),
3833 Pragma_Name
=> Name_Max_Entry_Queue_Length
);
3835 Decorate
(Aspect
, Aitem
);
3836 Insert_Pragma
(Aitem
);
3841 when Aspect_Max_Queue_Length
=>
3842 Aitem
:= Make_Aitem_Pragma
3843 (Pragma_Argument_Associations
=> New_List
(
3844 Make_Pragma_Argument_Association
(Loc
,
3845 Expression
=> Relocate_Node
(Expr
))),
3846 Pragma_Name
=> Name_Max_Queue_Length
);
3848 Decorate
(Aspect
, Aitem
);
3849 Insert_Pragma
(Aitem
);
3852 -- Aspect No_Caching is never delayed because it is equivalent
3853 -- to a source pragma which appears after the related object
3856 when Aspect_No_Caching
=>
3857 Aitem
:= Make_Aitem_Pragma
3858 (Pragma_Argument_Associations
=> New_List
(
3859 Make_Pragma_Argument_Association
(Loc
,
3860 Expression
=> Relocate_Node
(Expr
))),
3861 Pragma_Name
=> Name_No_Caching
);
3863 Decorate
(Aspect
, Aitem
);
3864 Insert_Pragma
(Aitem
);
3867 -- No_Controlled_Parts, No_Task_Parts
3869 when Aspect_No_Controlled_Parts | Aspect_No_Task_Parts
=>
3871 -- Check appropriate type argument
3873 if not Is_Type
(E
) then
3875 ("aspect % can only be applied to types", E
);
3878 -- Disallow subtypes
3880 if Nkind
(Declaration_Node
(E
)) = N_Subtype_Declaration
then
3882 ("aspect % cannot be applied to subtypes", E
);
3885 -- Resolve the expression to a boolean
3887 if Present
(Expr
) then
3888 Check_Expr_Is_OK_Static_Expression
(Expr
, Any_Boolean
);
3895 when Aspect_Obsolescent
=> declare
3903 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3904 Expression
=> Relocate_Node
(Expr
)));
3907 Aitem
:= Make_Aitem_Pragma
3908 (Pragma_Argument_Associations
=> Args
,
3909 Pragma_Name
=> Name_Obsolescent
);
3914 when Aspect_Part_Of
=>
3915 if Nkind
(N
) in N_Object_Declaration
3916 | N_Package_Instantiation
3917 or else Is_Single_Concurrent_Type_Declaration
(N
)
3919 Aitem
:= Make_Aitem_Pragma
3920 (Pragma_Argument_Associations
=> New_List
(
3921 Make_Pragma_Argument_Association
(Loc
,
3922 Expression
=> Relocate_Node
(Expr
))),
3923 Pragma_Name
=> Name_Part_Of
);
3925 Decorate
(Aspect
, Aitem
);
3926 Insert_Pragma
(Aitem
);
3930 ("aspect & must apply to package instantiation, "
3931 & "object, single protected type or single task type",
3939 when Aspect_SPARK_Mode
=>
3940 Aitem
:= Make_Aitem_Pragma
3941 (Pragma_Argument_Associations
=> New_List
(
3942 Make_Pragma_Argument_Association
(Loc
,
3943 Expression
=> Relocate_Node
(Expr
))),
3944 Pragma_Name
=> Name_SPARK_Mode
);
3946 Decorate
(Aspect
, Aitem
);
3947 Insert_Pragma
(Aitem
);
3952 -- Aspect Refined_Depends is never delayed because it is
3953 -- equivalent to a source pragma which appears in the
3954 -- declarations of the related subprogram body. To deal with
3955 -- forward references, the generated pragma is stored in the
3956 -- contract of the related subprogram body and later analyzed
3957 -- at the end of the declarative region. For details, see
3958 -- routine Analyze_Refined_Depends_In_Decl_Part.
3960 when Aspect_Refined_Depends
=>
3961 Aitem
:= Make_Aitem_Pragma
3962 (Pragma_Argument_Associations
=> New_List
(
3963 Make_Pragma_Argument_Association
(Loc
,
3964 Expression
=> Relocate_Node
(Expr
))),
3965 Pragma_Name
=> Name_Refined_Depends
);
3967 Decorate
(Aspect
, Aitem
);
3968 Insert_Pragma
(Aitem
);
3973 -- Aspect Refined_Global is never delayed because it is
3974 -- equivalent to a source pragma which appears in the
3975 -- declarations of the related subprogram body. To deal with
3976 -- forward references, the generated pragma is stored in the
3977 -- contract of the related subprogram body and later analyzed
3978 -- at the end of the declarative region. For details, see
3979 -- routine Analyze_Refined_Global_In_Decl_Part.
3981 when Aspect_Refined_Global
=>
3982 Aitem
:= Make_Aitem_Pragma
3983 (Pragma_Argument_Associations
=> New_List
(
3984 Make_Pragma_Argument_Association
(Loc
,
3985 Expression
=> Relocate_Node
(Expr
))),
3986 Pragma_Name
=> Name_Refined_Global
);
3988 Decorate
(Aspect
, Aitem
);
3989 Insert_Pragma
(Aitem
);
3994 when Aspect_Refined_Post
=>
3995 Aitem
:= Make_Aitem_Pragma
3996 (Pragma_Argument_Associations
=> New_List
(
3997 Make_Pragma_Argument_Association
(Loc
,
3998 Expression
=> Relocate_Node
(Expr
))),
3999 Pragma_Name
=> Name_Refined_Post
);
4001 Decorate
(Aspect
, Aitem
);
4002 Insert_Pragma
(Aitem
);
4007 when Aspect_Refined_State
=>
4009 -- The corresponding pragma for Refined_State is inserted in
4010 -- the declarations of the related package body. This action
4011 -- synchronizes both the source and from-aspect versions of
4014 if Nkind
(N
) = N_Package_Body
then
4015 Aitem
:= Make_Aitem_Pragma
4016 (Pragma_Argument_Associations
=> New_List
(
4017 Make_Pragma_Argument_Association
(Loc
,
4018 Expression
=> Relocate_Node
(Expr
))),
4019 Pragma_Name
=> Name_Refined_State
);
4021 Decorate
(Aspect
, Aitem
);
4022 Insert_Pragma
(Aitem
);
4024 -- Otherwise the context is illegal
4028 ("aspect & must apply to a package body", Aspect
, Id
);
4033 -- Relative_Deadline
4035 when Aspect_Relative_Deadline
=>
4036 Aitem
:= Make_Aitem_Pragma
4037 (Pragma_Argument_Associations
=> New_List
(
4038 Make_Pragma_Argument_Association
(Loc
,
4039 Expression
=> Relocate_Node
(Expr
))),
4040 Pragma_Name
=> Name_Relative_Deadline
);
4042 -- If the aspect applies to a task, the corresponding pragma
4043 -- must appear within its declarations, not after.
4045 if Nkind
(N
) = N_Task_Type_Declaration
then
4051 if No
(Task_Definition
(N
)) then
4052 Set_Task_Definition
(N
,
4053 Make_Task_Definition
(Loc
,
4054 Visible_Declarations
=> New_List
,
4055 End_Label
=> Empty
));
4058 Def
:= Task_Definition
(N
);
4059 V
:= Visible_Declarations
(Def
);
4060 if not Is_Empty_List
(V
) then
4061 Insert_Before
(First
(V
), Aitem
);
4064 Set_Visible_Declarations
(Def
, New_List
(Aitem
));
4071 -- Relaxed_Initialization
4073 when Aspect_Relaxed_Initialization
=>
4074 Analyze_Aspect_Relaxed_Initialization
;
4077 -- Secondary_Stack_Size
4079 -- Aspect Secondary_Stack_Size needs to be converted into a
4080 -- pragma for two reasons: the attribute is not analyzed until
4081 -- after the expansion of the task type declaration and the
4082 -- attribute does not have visibility on the discriminant.
4084 when Aspect_Secondary_Stack_Size
=>
4085 Aitem
:= Make_Aitem_Pragma
4086 (Pragma_Argument_Associations
=> New_List
(
4087 Make_Pragma_Argument_Association
(Loc
,
4088 Expression
=> Relocate_Node
(Expr
))),
4090 Name_Secondary_Stack_Size
);
4092 Decorate
(Aspect
, Aitem
);
4093 Insert_Pragma
(Aitem
);
4096 -- Volatile_Function
4098 -- Aspect Volatile_Function is never delayed because it is
4099 -- equivalent to a source pragma which appears after the
4100 -- related subprogram.
4102 when Aspect_Volatile_Function
=>
4103 Aitem
:= Make_Aitem_Pragma
4104 (Pragma_Argument_Associations
=> New_List
(
4105 Make_Pragma_Argument_Association
(Loc
,
4106 Expression
=> Relocate_Node
(Expr
))),
4107 Pragma_Name
=> Name_Volatile_Function
);
4109 Decorate
(Aspect
, Aitem
);
4110 Insert_Pragma
(Aitem
);
4113 -- Case 2e: Annotate aspect
4115 when Aspect_Annotate | Aspect_GNAT_Annotate
=>
4122 -- The argument can be a single identifier
4124 if Nkind
(Expr
) = N_Identifier
then
4126 -- One level of parens is allowed
4128 if Paren_Count
(Expr
) > 1 then
4129 Error_Msg_F
("extra parentheses ignored", Expr
);
4132 Set_Paren_Count
(Expr
, 0);
4134 -- Add the single item to the list
4136 Args
:= New_List
(Expr
);
4138 -- Otherwise we must have an aggregate
4140 elsif Nkind
(Expr
) = N_Aggregate
then
4142 -- Must be positional
4144 if Present
(Component_Associations
(Expr
)) then
4146 ("purely positional aggregate required", Expr
);
4150 -- Must not be parenthesized
4152 if Paren_Count
(Expr
) /= 0 then
4153 Error_Msg_F
-- CODEFIX
4154 ("redundant parentheses", Expr
);
4157 -- List of arguments is list of aggregate expressions
4159 Args
:= Expressions
(Expr
);
4161 -- Anything else is illegal
4164 Error_Msg_F
("wrong form for Annotate aspect", Expr
);
4168 -- Prepare pragma arguments
4171 Arg
:= First
(Args
);
4172 while Present
(Arg
) loop
4174 Make_Pragma_Argument_Association
(Sloc
(Arg
),
4175 Expression
=> Relocate_Node
(Arg
)));
4180 Make_Pragma_Argument_Association
(Sloc
(Ent
),
4181 Chars
=> Name_Entity
,
4182 Expression
=> Ent
));
4184 Aitem
:= Make_Aitem_Pragma
4185 (Pragma_Argument_Associations
=> Pargs
,
4186 Pragma_Name
=> Name_Annotate
);
4189 -- Case 3 : Aspects that don't correspond to pragma/attribute
4190 -- definition clause.
4192 -- Case 3a: The aspects listed below don't correspond to
4193 -- pragmas/attributes but do require delayed analysis.
4195 when Aspect_Default_Value | Aspect_Default_Component_Value
=>
4196 Error_Msg_Name_1
:= Nam
;
4198 if not Is_Type
(E
) then
4199 Error_Msg_N
("aspect% can only apply to a type", Id
);
4202 elsif not Is_First_Subtype
(E
) then
4203 Error_Msg_N
("aspect% cannot apply to subtype", Id
);
4206 elsif A_Id
= Aspect_Default_Value
4207 and then not Is_Scalar_Type
(E
)
4210 ("aspect% can only be applied to scalar type", Id
);
4213 elsif A_Id
= Aspect_Default_Component_Value
then
4214 if not Is_Array_Type
(E
) then
4216 ("aspect% can only be applied to array type", Id
);
4219 elsif not Is_Scalar_Type
(Component_Type
(E
)) then
4220 Error_Msg_N
("aspect% requires scalar components", Id
);
4227 when Aspect_Aggregate
=>
4228 -- We will be checking that the aspect is not specified on a
4229 -- non-array type in Check_Aspect_At_Freeze_Point
4231 Validate_Aspect_Aggregate
(Expr
);
4232 Record_Rep_Item
(E
, Aspect
);
4235 when Aspect_Stable_Properties
=>
4236 Validate_Aspect_Stable_Properties
4237 (E
, Expr
, Class_Present
=> Class_Present
(Aspect
));
4238 Record_Rep_Item
(E
, Aspect
);
4241 when Aspect_Designated_Storage_Model
=>
4242 if not All_Extensions_Allowed
then
4243 Error_Msg_GNAT_Extension
("aspect %", Sloc
(Aspect
));
4245 elsif not Is_Type
(E
)
4246 or else Ekind
(E
) /= E_Access_Type
4249 ("can only be specified for pool-specific access type",
4253 Record_Rep_Item
(E
, Aspect
);
4256 when Aspect_Storage_Model_Type
=>
4257 if not All_Extensions_Allowed
then
4258 Error_Msg_GNAT_Extension
("aspect %", Sloc
(Aspect
));
4260 elsif not Is_Type
(E
)
4261 or else not Is_Immutably_Limited_Type
(E
)
4264 ("can only be specified for immutably limited type",
4268 Record_Rep_Item
(E
, Aspect
);
4271 when Aspect_Integer_Literal
4272 | Aspect_Real_Literal
4273 | Aspect_String_Literal
4276 if not Is_First_Subtype
(E
) then
4278 ("may only be specified for a first subtype", Aspect
);
4282 if Ada_Version
< Ada_2022
then
4284 (No_Implementation_Aspect_Specifications
, N
);
4289 -- Case 3b: The aspects listed below don't correspond to
4290 -- pragmas/attributes and don't need delayed analysis.
4292 -- Implicit_Dereference
4294 -- For Implicit_Dereference, External_Name and Link_Name, only
4295 -- the legality checks are done during the analysis, thus no
4296 -- delay is required.
4298 when Aspect_Implicit_Dereference
=>
4299 Analyze_Aspect_Implicit_Dereference
;
4304 when Aspect_Dimension
=>
4305 Analyze_Aspect_Dimension
(N
, Id
, Expr
);
4310 when Aspect_Dimension_System
=>
4311 Analyze_Aspect_Dimension_System
(N
, Id
, Expr
);
4314 -- Case 4: Aspects requiring special handling
4316 -- Pre/Post/Test_Case/Contract_Cases/Always_Terminates/
4317 -- Exceptional_Cases and Subprogram_Variant whose corresponding
4318 -- pragmas take care of the delay.
4322 -- Aspects Pre/Post generate Precondition/Postcondition pragmas
4323 -- with a first argument that is the expression, and a second
4324 -- argument that is an informative message if the test fails.
4325 -- This is inserted right after the declaration, to get the
4326 -- required pragma placement. The processing for the pragmas
4327 -- takes care of the required delay.
4329 when Pre_Post_Aspects
=> Pre_Post
: declare
4333 if A_Id
in Aspect_Pre | Aspect_Precondition
then
4334 Pname
:= Name_Precondition
;
4336 Pname
:= Name_Postcondition
;
4339 -- Check that the class-wide predicate cannot be applied to
4340 -- an operation of a synchronized type. AI12-0182 forbids
4341 -- these altogether, while earlier language semantics made
4342 -- them legal on tagged synchronized types.
4344 -- Other legality checks are performed when analyzing the
4345 -- contract of the operation.
4347 if Class_Present
(Aspect
)
4348 and then Is_Concurrent_Type
(Current_Scope
)
4349 and then Ekind
(E
) in E_Entry | E_Function | E_Procedure
4351 Error_Msg_Name_1
:= Original_Aspect_Pragma_Name
(Aspect
);
4353 ("aspect % can only be specified for a primitive "
4354 & "operation of a tagged type", Aspect
);
4359 -- Remember class-wide conditions; they will be merged
4360 -- with inherited conditions.
4362 if Class_Present
(Aspect
)
4363 and then A_Id
in Aspect_Pre | Aspect_Post
4364 and then Is_Subprogram
(E
)
4365 and then not Is_Ignored_Ghost_Entity
(E
)
4367 if A_Id
= Aspect_Pre
then
4368 if Is_Ignored
(Aspect
) then
4369 Set_Ignored_Class_Preconditions
(E
,
4370 New_Copy_Tree
(Expr
));
4372 Set_Class_Preconditions
(E
, New_Copy_Tree
(Expr
));
4375 -- Postconditions may split into separate aspects, and we
4376 -- remember the expression before such split (i.e. when
4377 -- the first postcondition is processed).
4379 elsif No
(Class_Postconditions
(E
))
4380 and then No
(Ignored_Class_Postconditions
(E
))
4382 if Is_Ignored
(Aspect
) then
4383 Set_Ignored_Class_Postconditions
(E
,
4384 New_Copy_Tree
(Expr
));
4386 Set_Class_Postconditions
(E
, New_Copy_Tree
(Expr
));
4391 -- If the expressions is of the form A and then B, then
4392 -- we generate separate Pre/Post aspects for the separate
4393 -- clauses. Since we allow multiple pragmas, there is no
4394 -- problem in allowing multiple Pre/Post aspects internally.
4395 -- These should be treated in reverse order (B first and
4396 -- A second) since they are later inserted just after N in
4397 -- the order they are treated. This way, the pragma for A
4398 -- ends up preceding the pragma for B, which may have an
4399 -- importance for the error raised (either constraint error
4400 -- or precondition error).
4402 -- We do not do this for Pre'Class, since we have to put
4403 -- these conditions together in a complex OR expression.
4405 -- We don't do this in GNATprove mode, because it brings no
4406 -- benefit for proof and causes annoyance for flow analysis,
4407 -- which prefers to be as close to the original source code
4408 -- as possible. Also we don't do this when analyzing generic
4409 -- units since it causes spurious visibility errors in the
4410 -- preanalysis of instantiations.
4412 if not GNATprove_Mode
4413 and then (Pname
= Name_Postcondition
4414 or else not Class_Present
(Aspect
))
4415 and then not Inside_A_Generic
4417 while Nkind
(Expr
) = N_And_Then
loop
4418 Insert_After
(Aspect
,
4419 Make_Aspect_Specification
(Sloc
(Left_Opnd
(Expr
)),
4420 Identifier
=> Identifier
(Aspect
),
4421 Expression
=> Relocate_Node
(Left_Opnd
(Expr
)),
4422 Class_Present
=> Class_Present
(Aspect
),
4423 Split_PPC
=> True));
4424 Rewrite
(Expr
, Relocate_Node
(Right_Opnd
(Expr
)));
4425 Eloc
:= Sloc
(Expr
);
4429 -- Build the precondition/postcondition pragma
4431 Aitem
:= Make_Aitem_Pragma
4432 (Pragma_Argument_Associations
=> New_List
(
4433 Make_Pragma_Argument_Association
(Eloc
,
4434 Chars
=> Name_Check
,
4435 Expression
=> Relocate_Expression
(Expr
))),
4436 Pragma_Name
=> Pname
);
4438 -- Add message unless exception messages are suppressed
4440 if not Opt
.Exception_Locations_Suppressed
then
4441 Append_To
(Pragma_Argument_Associations
(Aitem
),
4442 Make_Pragma_Argument_Association
(Eloc
,
4443 Chars
=> Name_Message
,
4445 Make_String_Literal
(Eloc
,
4447 & Get_Name_String
(Pname
)
4449 & Build_Location_String
(Eloc
))));
4452 Set_Is_Delayed_Aspect
(Aspect
);
4454 -- For Pre/Post cases, insert immediately after the entity
4455 -- declaration, since that is the required pragma placement.
4456 -- Note that for these aspects, we do not have to worry
4457 -- about delay issues, since the pragmas themselves deal
4458 -- with delay of visibility for the expression analysis.
4460 Insert_Pragma
(Aitem
);
4467 when Aspect_Test_Case
=> Test_Case
: declare
4469 Comp_Expr
: Node_Id
;
4470 Comp_Assn
: Node_Id
;
4475 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
4476 Error_Msg_Name_1
:= Nam
;
4477 Error_Msg_N
("incorrect placement of aspect %", E
);
4481 if Nkind
(Expr
) /= N_Aggregate
4482 or else Null_Record_Present
(Expr
)
4484 Error_Msg_Name_1
:= Nam
;
4486 ("wrong syntax for aspect % for &", Id
, E
);
4490 -- Check that the expression is a proper aggregate (no
4493 if Paren_Count
(Expr
) /= 0 then
4494 Error_Msg_F
-- CODEFIX
4495 ("redundant parentheses", Expr
);
4499 -- Create the list of arguments for building the Test_Case
4502 Comp_Expr
:= First
(Expressions
(Expr
));
4503 while Present
(Comp_Expr
) loop
4505 Make_Pragma_Argument_Association
(Sloc
(Comp_Expr
),
4506 Expression
=> Relocate_Node
(Comp_Expr
)));
4510 Comp_Assn
:= First
(Component_Associations
(Expr
));
4511 while Present
(Comp_Assn
) loop
4512 if List_Length
(Choices
(Comp_Assn
)) /= 1
4514 Nkind
(First
(Choices
(Comp_Assn
))) /= N_Identifier
4516 Error_Msg_Name_1
:= Nam
;
4518 ("wrong syntax for aspect % for &", Id
, E
);
4523 Make_Pragma_Argument_Association
(Sloc
(Comp_Assn
),
4524 Chars
=> Chars
(First
(Choices
(Comp_Assn
))),
4526 Relocate_Node
(Expression
(Comp_Assn
))));
4530 -- Build the test-case pragma
4532 Aitem
:= Make_Aitem_Pragma
4533 (Pragma_Argument_Associations
=> Args
,
4534 Pragma_Name
=> Name_Test_Case
);
4539 when Aspect_Contract_Cases
=>
4540 Aitem
:= Make_Aitem_Pragma
4541 (Pragma_Argument_Associations
=> New_List
(
4542 Make_Pragma_Argument_Association
(Loc
,
4543 Expression
=> Relocate_Node
(Expr
))),
4544 Pragma_Name
=> Name_Contract_Cases
);
4546 Decorate
(Aspect
, Aitem
);
4547 Insert_Pragma
(Aitem
);
4550 -- Always_Terminates
4552 when Aspect_Always_Terminates
=>
4553 Aitem
:= Make_Aitem_Pragma
4554 (Pragma_Argument_Associations
=> New_List
(
4555 Make_Pragma_Argument_Association
(Loc
,
4556 Expression
=> Relocate_Node
(Expr
))),
4557 Pragma_Name
=> Name_Always_Terminates
);
4559 Decorate
(Aspect
, Aitem
);
4560 Insert_Pragma
(Aitem
);
4563 -- Exceptional_Cases
4565 when Aspect_Exceptional_Cases
=>
4566 Aitem
:= Make_Aitem_Pragma
4567 (Pragma_Argument_Associations
=> New_List
(
4568 Make_Pragma_Argument_Association
(Loc
,
4569 Expression
=> Relocate_Node
(Expr
))),
4570 Pragma_Name
=> Name_Exceptional_Cases
);
4572 Decorate
(Aspect
, Aitem
);
4573 Insert_Pragma
(Aitem
);
4576 -- Subprogram_Variant
4578 when Aspect_Subprogram_Variant
=>
4579 Aitem
:= Make_Aitem_Pragma
4580 (Pragma_Argument_Associations
=> New_List
(
4581 Make_Pragma_Argument_Association
(Loc
,
4582 Expression
=> Relocate_Node
(Expr
))),
4583 Pragma_Name
=> Name_Subprogram_Variant
);
4585 Decorate
(Aspect
, Aitem
);
4586 Insert_Pragma
(Aitem
);
4589 -- Case 5: Special handling for aspects with an optional
4590 -- boolean argument.
4592 -- In the delayed case, the corresponding pragma cannot be
4593 -- generated yet because the evaluation of the boolean needs
4594 -- to be delayed till the freeze point.
4596 when Boolean_Aspects
4597 | Library_Unit_Aspects
4599 Set_Is_Boolean_Aspect
(Aspect
);
4601 -- Lock_Free aspect only apply to protected objects
4603 if A_Id
= Aspect_Lock_Free
then
4604 if Ekind
(E
) /= E_Protected_Type
then
4605 Error_Msg_Name_1
:= Nam
;
4607 ("aspect % only applies to a protected type " &
4612 -- Set the Uses_Lock_Free flag to True if there is no
4613 -- expression or if the expression is True. The
4614 -- evaluation of this aspect should be delayed to the
4615 -- freeze point if we wanted to handle the corner case
4616 -- of "true" or "false" being redefined.
4619 or else Is_True
(Static_Boolean
(Expr
))
4621 Set_Uses_Lock_Free
(E
);
4624 Record_Rep_Item
(E
, Aspect
);
4629 elsif A_Id
in Aspect_Export | Aspect_Import
then
4630 Analyze_Aspect_Export_Import
;
4632 -- Disable_Controlled
4634 elsif A_Id
= Aspect_Disable_Controlled
then
4635 Analyze_Aspect_Disable_Controlled
;
4638 -- Ada 2022 (AI12-0129): Exclusive_Functions
4640 elsif A_Id
= Aspect_Exclusive_Functions
then
4641 if Ekind
(E
) /= E_Protected_Type
then
4642 Error_Msg_Name_1
:= Nam
;
4644 ("aspect % only applies to a protected type " &
4651 -- Ada 2022 (AI12-0363): Full_Access_Only
4653 elsif A_Id
= Aspect_Full_Access_Only
then
4654 Error_Msg_Ada_2022_Feature
("aspect %", Sloc
(Aspect
));
4656 -- Ada 2022 (AI12-0075): static expression functions
4658 elsif A_Id
= Aspect_Static
then
4659 Analyze_Aspect_Static
;
4662 -- Ada 2022 (AI12-0279)
4664 elsif A_Id
= Aspect_Yield
then
4665 Analyze_Aspect_Yield
;
4669 -- Library unit aspects require special handling in the case
4670 -- of a package declaration, the pragma needs to be inserted
4671 -- in the list of declarations for the associated package.
4672 -- There is no issue of visibility delay for these aspects.
4674 if A_Id
in Library_Unit_Aspects
4676 Nkind
(N
) in N_Package_Declaration
4677 | N_Generic_Package_Declaration
4678 and then Nkind
(Parent
(N
)) /= N_Compilation_Unit
4680 -- Aspect is legal on a local instantiation of a library-
4681 -- level generic unit.
4683 and then not Is_Generic_Instance
(Defining_Entity
(N
))
4686 ("incorrect context for library unit aspect&", Id
);
4690 -- Cases where we do not delay
4692 if not Delay_Required
then
4694 -- Exclude aspects Export and Import because their pragma
4695 -- syntax does not map directly to a Boolean aspect.
4697 if A_Id
not in Aspect_Export | Aspect_Import
then
4698 Aitem
:= Make_Aitem_Pragma
4699 (Pragma_Argument_Associations
=> New_List
(
4700 Make_Pragma_Argument_Association
(Sloc
(Ent
),
4701 Expression
=> Ent
)),
4702 Pragma_Name
=> Nam
);
4705 -- In general cases, the corresponding pragma/attribute
4706 -- definition clause will be inserted later at the freezing
4707 -- point, and we do not need to build it now.
4715 -- This is special because for access types we need to generate
4716 -- an attribute definition clause. This also works for single
4717 -- task declarations, but it does not work for task type
4718 -- declarations, because we have the case where the expression
4719 -- references a discriminant of the task type. That can't use
4720 -- an attribute definition clause because we would not have
4721 -- visibility on the discriminant. For that case we must
4722 -- generate a pragma in the task definition.
4724 when Aspect_Storage_Size
=>
4728 if Ekind
(E
) = E_Task_Type
then
4730 Decl
: constant Node_Id
:= Declaration_Node
(E
);
4733 pragma Assert
(Nkind
(Decl
) = N_Task_Type_Declaration
);
4735 -- If no task definition, create one
4737 if No
(Task_Definition
(Decl
)) then
4738 Set_Task_Definition
(Decl
,
4739 Make_Task_Definition
(Loc
,
4740 Visible_Declarations
=> Empty_List
,
4741 End_Label
=> Empty
));
4744 -- Create a pragma and put it at the start of the task
4745 -- definition for the task type declaration.
4747 Aitem
:= Make_Aitem_Pragma
4748 (Pragma_Argument_Associations
=> New_List
(
4749 Make_Pragma_Argument_Association
(Loc
,
4750 Expression
=> Relocate_Node
(Expr
))),
4751 Pragma_Name
=> Name_Storage_Size
);
4755 Visible_Declarations
(Task_Definition
(Decl
)));
4759 -- All other cases, generate attribute definition
4763 Make_Attribute_Definition_Clause
(Loc
,
4765 Chars
=> Name_Storage_Size
,
4766 Expression
=> Relocate_Node
(Expr
));
4770 -- Attach the corresponding pragma/attribute definition clause to
4771 -- the aspect specification node.
4773 if Present
(Aitem
) then
4774 Set_From_Aspect_Specification
(Aitem
);
4777 -- For an aspect that applies to a type, indicate whether it
4778 -- appears on a partial view of the type.
4780 if Is_Type
(E
) and then Is_Private_Type
(E
) then
4781 Set_Aspect_On_Partial_View
(Aspect
);
4784 -- In the context of a compilation unit, we directly put the
4785 -- pragma in the Pragmas_After list of the N_Compilation_Unit_Aux
4786 -- node (no delay is required here) except for aspects on a
4787 -- subprogram body (see below) and a generic package, for which we
4788 -- need to introduce the pragma before building the generic copy
4789 -- (see sem_ch12), and for package instantiations, where the
4790 -- library unit pragmas are better handled early.
4792 if Nkind
(Parent
(N
)) = N_Compilation_Unit
4793 and then (Present
(Aitem
) or else Is_Boolean_Aspect
(Aspect
))
4796 Aux
: constant Node_Id
:= Aux_Decls_Node
(Parent
(N
));
4799 pragma Assert
(Nkind
(Aux
) = N_Compilation_Unit_Aux
);
4801 -- For a Boolean aspect, create the corresponding pragma if
4802 -- no expression or if the value is True.
4804 if Is_Boolean_Aspect
(Aspect
) and then No
(Aitem
) then
4805 if Is_True
(Static_Boolean
(Expr
)) then
4806 Aitem
:= Make_Aitem_Pragma
4807 (Pragma_Argument_Associations
=> New_List
(
4808 Make_Pragma_Argument_Association
(Sloc
(Ent
),
4809 Expression
=> Ent
)),
4810 Pragma_Name
=> Nam
);
4812 Set_From_Aspect_Specification
(Aitem
, True);
4813 Set_Corresponding_Aspect
(Aitem
, Aspect
);
4820 -- If the aspect is on a subprogram body (relevant aspect
4821 -- is Inline), add the pragma in front of the declarations.
4823 if Nkind
(N
) = N_Subprogram_Body
then
4824 if No
(Declarations
(N
)) then
4825 Set_Declarations
(N
, New_List
);
4828 Prepend
(Aitem
, Declarations
(N
));
4830 elsif Nkind
(N
) = N_Generic_Package_Declaration
then
4831 if No
(Visible_Declarations
(Specification
(N
))) then
4832 Set_Visible_Declarations
(Specification
(N
), New_List
);
4836 Visible_Declarations
(Specification
(N
)));
4838 elsif Nkind
(N
) = N_Package_Instantiation
then
4840 Spec
: constant Node_Id
:=
4841 Specification
(Instance_Spec
(N
));
4843 if No
(Visible_Declarations
(Spec
)) then
4844 Set_Visible_Declarations
(Spec
, New_List
);
4847 Prepend
(Aitem
, Visible_Declarations
(Spec
));
4851 if No
(Pragmas_After
(Aux
)) then
4852 Set_Pragmas_After
(Aux
, New_List
);
4855 Append
(Aitem
, Pragmas_After
(Aux
));
4862 -- The evaluation of the aspect is delayed to the freezing point.
4863 -- The pragma or attribute clause if there is one is then attached
4864 -- to the aspect specification which is put in the rep item list.
4866 if Delay_Required
then
4867 if Present
(Aitem
) then
4868 Set_Is_Delayed_Aspect
(Aitem
);
4869 Set_Aspect_Rep_Item
(Aspect
, Aitem
);
4870 Set_Parent
(Aitem
, Aspect
);
4873 Set_Is_Delayed_Aspect
(Aspect
);
4875 -- In the case of Default_Value, link the aspect to base type
4876 -- as well, even though it appears on a first subtype. This is
4877 -- mandated by the semantics of the aspect. Do not establish
4878 -- the link when processing the base type itself as this leads
4879 -- to a rep item circularity.
4881 if A_Id
= Aspect_Default_Value
and then Base_Type
(E
) /= E
then
4882 Set_Has_Delayed_Aspects
(Base_Type
(E
));
4883 Record_Rep_Item
(Base_Type
(E
), Aspect
);
4886 Set_Has_Delayed_Aspects
(E
);
4887 Record_Rep_Item
(E
, Aspect
);
4889 -- When delay is not required and the context is a package or a
4890 -- subprogram body, insert the pragma in the body declarations.
4892 elsif Nkind
(N
) in N_Package_Body | N_Subprogram_Body
then
4893 if No
(Declarations
(N
)) then
4894 Set_Declarations
(N
, New_List
);
4897 -- The pragma is added before source declarations
4899 Prepend_To
(Declarations
(N
), Aitem
);
4901 -- When delay is not required and the context is not a compilation
4902 -- unit, we simply insert the pragma/attribute definition clause
4905 elsif Present
(Aitem
) then
4906 Insert_After
(Ins_Node
, Aitem
);
4912 -- If a nonoverridable aspect is explicitly specified for a
4913 -- derived type, then check consistency with the parent type.
4915 if A_Id
in Nonoverridable_Aspect_Id
4916 and then Nkind
(N
) = N_Full_Type_Declaration
4917 and then Nkind
(Type_Definition
(N
)) = N_Derived_Type_Definition
4918 and then not In_Instance_Body
4921 Parent_Type
: constant Entity_Id
:= Etype
(E
);
4922 Inherited_Aspect
: constant Node_Id
:=
4923 Find_Aspect
(Parent_Type
, A_Id
);
4925 if Present
(Inherited_Aspect
)
4926 and then not Is_Confirming
4927 (A_Id
, Inherited_Aspect
, Aspect
)
4929 Error_Msg_Name_1
:= Aspect_Names
(A_Id
);
4930 Error_Msg_Sloc
:= Sloc
(Inherited_Aspect
);
4933 ("overriding aspect specification for "
4934 & "nonoverridable aspect % does not confirm "
4935 & "aspect specification inherited from #",
4941 when Aspect_Exit
=> null;
4942 end Analyze_One_Aspect
;
4945 end loop Aspect_Loop
;
4947 if Has_Delayed_Aspects
(E
) then
4948 Ensure_Freeze_Node
(E
);
4950 end Analyze_Aspect_Specifications
;
4952 ------------------------------------------------
4953 -- Analyze_Aspects_On_Subprogram_Body_Or_Stub --
4954 ------------------------------------------------
4956 procedure Analyze_Aspects_On_Subprogram_Body_Or_Stub
(N
: Node_Id
) is
4957 Body_Id
: constant Entity_Id
:= Defining_Entity
(N
);
4959 procedure Diagnose_Misplaced_Aspects
(Spec_Id
: Entity_Id
);
4960 -- Body [stub] N has aspects, but they are not properly placed. Emit an
4961 -- error message depending on the aspects involved. Spec_Id denotes the
4962 -- entity of the corresponding spec.
4964 --------------------------------
4965 -- Diagnose_Misplaced_Aspects --
4966 --------------------------------
4968 procedure Diagnose_Misplaced_Aspects
(Spec_Id
: Entity_Id
) is
4969 procedure Misplaced_Aspect_Error
4972 -- Emit an error message concerning misplaced aspect Asp. Ref_Nam is
4973 -- the name of the refined version of the aspect.
4975 ----------------------------
4976 -- Misplaced_Aspect_Error --
4977 ----------------------------
4979 procedure Misplaced_Aspect_Error
4983 Asp_Nam
: constant Name_Id
:= Chars
(Identifier
(Asp
));
4984 Asp_Id
: constant Aspect_Id
:= Get_Aspect_Id
(Asp_Nam
);
4987 -- The corresponding spec already contains the aspect in question
4988 -- and the one appearing on the body must be the refined form:
4990 -- procedure P with Global ...;
4991 -- procedure P with Global ... is ... end P;
4995 if Has_Aspect
(Spec_Id
, Asp_Id
) then
4996 Error_Msg_Name_1
:= Asp_Nam
;
4998 -- Subunits cannot carry aspects that apply to a subprogram
5001 if Nkind
(Parent
(N
)) = N_Subunit
then
5002 Error_Msg_N
("aspect % cannot apply to a subunit", Asp
);
5004 -- Otherwise suggest the refined form
5007 Error_Msg_Name_2
:= Ref_Nam
;
5008 Error_Msg_N
("aspect % should be %", Asp
);
5011 -- Otherwise the aspect must appear on the spec, not on the body
5014 -- procedure P with Global ... is ... end P;
5018 ("aspect specification must appear on initial declaration",
5021 end Misplaced_Aspect_Error
;
5028 -- Start of processing for Diagnose_Misplaced_Aspects
5031 -- Iterate over the aspect specifications and emit specific errors
5032 -- where applicable.
5034 Asp
:= First
(Aspect_Specifications
(N
));
5035 while Present
(Asp
) loop
5036 Asp_Nam
:= Chars
(Identifier
(Asp
));
5038 -- Do not emit errors on aspects that can appear on a subprogram
5039 -- body. This scenario occurs when the aspect specification list
5040 -- contains both misplaced and properly placed aspects.
5042 if Aspect_On_Body_Or_Stub_OK
(Get_Aspect_Id
(Asp_Nam
)) then
5045 -- Special diagnostics for SPARK aspects
5047 elsif Asp_Nam
= Name_Depends
then
5048 Misplaced_Aspect_Error
(Asp
, Name_Refined_Depends
);
5050 elsif Asp_Nam
= Name_Global
then
5051 Misplaced_Aspect_Error
(Asp
, Name_Refined_Global
);
5053 elsif Asp_Nam
= Name_Post
then
5054 Misplaced_Aspect_Error
(Asp
, Name_Refined_Post
);
5056 -- Otherwise a language-defined aspect is misplaced
5060 ("aspect specification must appear on initial declaration",
5066 end Diagnose_Misplaced_Aspects
;
5070 Spec_Id
: constant Entity_Id
:= Unique_Defining_Entity
(N
);
5072 -- Start of processing for Analyze_Aspects_On_Subprogram_Body_Or_Stub
5075 -- Language-defined aspects cannot be associated with a subprogram body
5076 -- [stub] if the subprogram has a spec. Certain implementation defined
5077 -- aspects are allowed to break this rule (for all applicable cases, see
5078 -- table Aspects.Aspect_On_Body_Or_Stub_OK).
5080 if Spec_Id
/= Body_Id
and then not Aspects_On_Body_Or_Stub_OK
(N
) then
5081 Diagnose_Misplaced_Aspects
(Spec_Id
);
5083 Analyze_Aspect_Specifications
(N
, Body_Id
);
5085 end Analyze_Aspects_On_Subprogram_Body_Or_Stub
;
5087 -----------------------
5088 -- Analyze_At_Clause --
5089 -----------------------
5091 -- An at clause is replaced by the corresponding Address attribute
5092 -- definition clause that is the preferred approach in Ada 95.
5094 procedure Analyze_At_Clause
(N
: Node_Id
) is
5095 CS
: constant Boolean := Comes_From_Source
(N
);
5098 -- This is an obsolescent feature
5100 Check_Restriction
(No_Obsolescent_Features
, N
);
5102 if Warn_On_Obsolescent_Feature
then
5104 ("?j?at clause is an obsolescent feature (RM J.7(2))", N
);
5106 ("\?j?use address attribute definition clause instead", N
);
5109 -- Rewrite as address clause
5112 Make_Attribute_Definition_Clause
(Sloc
(N
),
5113 Name
=> Identifier
(N
),
5114 Chars
=> Name_Address
,
5115 Expression
=> Expression
(N
)));
5117 -- We preserve Comes_From_Source, since logically the clause still comes
5118 -- from the source program even though it is changed in form.
5120 Set_Comes_From_Source
(N
, CS
);
5122 -- Analyze rewritten clause
5124 Analyze_Attribute_Definition_Clause
(N
);
5125 end Analyze_At_Clause
;
5127 -----------------------------------------
5128 -- Analyze_Attribute_Definition_Clause --
5129 -----------------------------------------
5131 procedure Analyze_Attribute_Definition_Clause
(N
: Node_Id
) is
5132 Loc
: constant Source_Ptr
:= Sloc
(N
);
5133 Nam
: constant Node_Id
:= Name
(N
);
5134 Attr
: constant Name_Id
:= Chars
(N
);
5135 Expr
: constant Node_Id
:= Expression
(N
);
5136 Id
: constant Attribute_Id
:= Get_Attribute_Id
(Attr
);
5139 -- The entity of Nam after it is analyzed. In the case of an incomplete
5140 -- type, this is the underlying type.
5143 -- The underlying entity to which the attribute applies. Generally this
5144 -- is the Underlying_Type of Ent, except in the case where the clause
5145 -- applies to the full view of an incomplete or private type, in which
5146 -- case U_Ent is just a copy of Ent.
5148 FOnly
: Boolean := False;
5149 -- Reset to True for subtype specific attribute (Alignment, Size)
5150 -- and for stream attributes, i.e. those cases where in the call to
5151 -- Rep_Item_Too_Late, FOnly is set True so that only the freezing rules
5152 -- are checked. Note that the case of stream attributes is not clear
5153 -- from the RM, but see AI95-00137. Also, the RM seems to disallow
5154 -- Storage_Size for derived task types, but that is also clearly
5157 procedure Analyze_Put_Image_TSS_Definition
;
5159 procedure Analyze_Stream_TSS_Definition
(TSS_Nam
: TSS_Name_Type
);
5160 -- Common processing for 'Read, 'Write, 'Input and 'Output attribute
5161 -- definition clauses.
5163 function Duplicate_Clause
return Boolean;
5164 -- This routine checks if the aspect for U_Ent being given by attribute
5165 -- definition clause N is for an aspect that has already been specified,
5166 -- and if so gives an error message. If there is a duplicate, True is
5167 -- returned, otherwise there is no error, and False is returned. Size
5168 -- and Value_Size are considered to conflict, but for compatibility,
5169 -- this is merely a warning.
5171 procedure Check_Indexing_Functions
;
5172 -- Check that the function in Constant_Indexing or Variable_Indexing
5173 -- attribute has the proper type structure. If the name is overloaded,
5174 -- check that some interpretation is legal.
5176 procedure Check_Iterator_Functions
;
5177 -- Check that there is a single function in Default_Iterator attribute
5178 -- that has the proper type structure.
5180 function Check_Primitive_Function
(Subp
: Entity_Id
) return Boolean;
5181 -- Common legality check for the previous two
5183 -----------------------------------
5184 -- Analyze_Put_Image_TSS_Definition --
5185 -----------------------------------
5187 procedure Analyze_Put_Image_TSS_Definition
is
5188 Subp
: Entity_Id
:= Empty
;
5193 function Has_Good_Profile
5195 Report
: Boolean := False) return Boolean;
5196 -- Return true if the entity is a subprogram with an appropriate
5197 -- profile for the attribute being defined. If result is False and
5198 -- Report is True, function emits appropriate error.
5200 ----------------------
5201 -- Has_Good_Profile --
5202 ----------------------
5204 function Has_Good_Profile
5206 Report
: Boolean := False) return Boolean
5212 if Ekind
(Subp
) /= E_Procedure
then
5216 F
:= First_Formal
(Subp
);
5222 if Base_Type
(Etype
(F
))
5223 /= Class_Wide_Type
(RTE
(RE_Root_Buffer_Type
))
5227 ("wrong type for Put_Image procedure''s first parameter",
5228 Parameter_Type
(Parent
(F
)));
5234 if Parameter_Mode
(F
) /= E_In_Out_Parameter
then
5237 ("wrong mode for Put_Image procedure''s first parameter",
5248 -- Verify that the prefix of the attribute and the local name for
5249 -- the type of the formal match.
5251 if Base_Type
(Typ
) /= Base_Type
(Ent
) then
5254 ("wrong type for Put_Image procedure''s second parameter",
5255 Parameter_Type
(Parent
(F
)));
5261 if Parameter_Mode
(F
) /= E_In_Parameter
then
5264 ("wrong mode for Put_Image procedure''s second parameter",
5271 if Present
(Next_Formal
(F
)) then
5276 end Has_Good_Profile
;
5278 -- Start of processing for Analyze_Put_Image_TSS_Definition
5281 if not Is_Type
(U_Ent
) then
5282 Error_Msg_N
("local name must be a subtype", Nam
);
5285 elsif not Is_First_Subtype
(U_Ent
) then
5286 Error_Msg_N
("local name must be a first subtype", Nam
);
5290 Pnam
:= TSS
(Base_Type
(U_Ent
), TSS_Put_Image
);
5292 -- If Pnam is present, it can be either inherited from an ancestor
5293 -- type (in which case it is legal to redefine it for this type), or
5294 -- be a previous definition of the attribute for the same type (in
5295 -- which case it is illegal).
5297 -- In the first case, it will have been analyzed already, and we can
5298 -- check that its profile does not match the expected profile for the
5299 -- Put_Image attribute of U_Ent. In the second case, either Pnam has
5300 -- been analyzed (and has the expected profile), or it has not been
5301 -- analyzed yet (case of a type that has not been frozen yet and for
5302 -- which Put_Image has been set using Set_TSS).
5305 and then (No
(First_Entity
(Pnam
)) or else Has_Good_Profile
(Pnam
))
5307 Error_Msg_Sloc
:= Sloc
(Pnam
);
5308 Error_Msg_Name_1
:= Attr
;
5309 Error_Msg_N
("% attribute already defined #", Nam
);
5315 if Is_Entity_Name
(Expr
) then
5316 if not Is_Overloaded
(Expr
) then
5317 if Has_Good_Profile
(Entity
(Expr
), Report
=> True) then
5318 Subp
:= Entity
(Expr
);
5322 Get_First_Interp
(Expr
, I
, It
);
5323 while Present
(It
.Nam
) loop
5324 if Has_Good_Profile
(It
.Nam
) then
5329 Get_Next_Interp
(I
, It
);
5334 if Present
(Subp
) then
5335 if Is_Abstract_Subprogram
(Subp
) then
5336 Error_Msg_N
("Put_Image subprogram must not be abstract", Expr
);
5340 Set_Entity
(Expr
, Subp
);
5341 Set_Etype
(Expr
, Etype
(Subp
));
5343 New_Put_Image_Subprogram
(N
, U_Ent
, Subp
);
5346 Error_Msg_Name_1
:= Attr
;
5347 Error_Msg_N
("incorrect expression for% attribute", Expr
);
5349 end Analyze_Put_Image_TSS_Definition
;
5351 -----------------------------------
5352 -- Analyze_Stream_TSS_Definition --
5353 -----------------------------------
5355 procedure Analyze_Stream_TSS_Definition
(TSS_Nam
: TSS_Name_Type
) is
5356 Subp
: Entity_Id
:= Empty
;
5361 Is_Read
: constant Boolean := (TSS_Nam
= TSS_Stream_Read
);
5362 -- True for Read attribute, False for other attributes
5364 function Has_Good_Profile
5366 Report
: Boolean := False) return Boolean;
5367 -- Return true if the entity is a subprogram with an appropriate
5368 -- profile for the attribute being defined. If result is False and
5369 -- Report is True, function emits appropriate error.
5371 ----------------------
5372 -- Has_Good_Profile --
5373 ----------------------
5375 function Has_Good_Profile
5377 Report
: Boolean := False) return Boolean
5379 Expected_Ekind
: constant array (Boolean) of Entity_Kind
:=
5380 (False => E_Procedure
, True => E_Function
);
5381 Is_Function
: constant Boolean := (TSS_Nam
= TSS_Stream_Input
);
5386 if Ekind
(Subp
) /= Expected_Ekind
(Is_Function
) then
5390 F
:= First_Formal
(Subp
);
5393 or else Ekind
(Etype
(F
)) /= E_Anonymous_Access_Type
5394 or else Base_Type
(Designated_Type
(Etype
(F
))) /=
5395 Class_Wide_Type
(RTE
(RE_Root_Stream_Type
))
5400 if not Is_Function
then
5404 Expected_Mode
: constant array (Boolean) of Entity_Kind
:=
5405 (False => E_In_Parameter
,
5406 True => E_Out_Parameter
);
5408 if Parameter_Mode
(F
) /= Expected_Mode
(Is_Read
) then
5416 Typ
:= Etype
(Subp
);
5419 -- Verify that the prefix of the attribute and the local name for
5420 -- the type of the formal match.
5422 if Base_Type
(Typ
) /= Base_Type
(Ent
) then
5426 if Present
(Next_Formal
(F
)) then
5429 elsif not Is_Scalar_Type
(Typ
)
5430 and then not Is_First_Subtype
(Typ
)
5431 and then not Is_Class_Wide_Type
(Typ
)
5433 if Report
and not Is_First_Subtype
(Typ
) then
5435 ("subtype of formal in stream operation must be a first "
5436 & "subtype", Parameter_Type
(Parent
(F
)));
5444 end Has_Good_Profile
;
5446 -- Start of processing for Analyze_Stream_TSS_Definition
5451 if not Is_Type
(U_Ent
) then
5452 Error_Msg_N
("local name must be a subtype", Nam
);
5455 elsif not Is_First_Subtype
(U_Ent
) then
5456 Error_Msg_N
("local name must be a first subtype", Nam
);
5460 Pnam
:= TSS
(Base_Type
(U_Ent
), TSS_Nam
);
5462 -- If Pnam is present, it can be either inherited from an ancestor
5463 -- type (in which case it is legal to redefine it for this type), or
5464 -- be a previous definition of the attribute for the same type (in
5465 -- which case it is illegal).
5467 -- In the first case, it will have been analyzed already, and we
5468 -- can check that its profile does not match the expected profile
5469 -- for a stream attribute of U_Ent. In the second case, either Pnam
5470 -- has been analyzed (and has the expected profile), or it has not
5471 -- been analyzed yet (case of a type that has not been frozen yet
5472 -- and for which the stream attribute has been set using Set_TSS).
5475 and then (No
(First_Entity
(Pnam
)) or else Has_Good_Profile
(Pnam
))
5477 Error_Msg_Sloc
:= Sloc
(Pnam
);
5478 Error_Msg_Name_1
:= Attr
;
5479 Error_Msg_N
("% attribute already defined #", Nam
);
5485 if Is_Entity_Name
(Expr
) then
5486 if not Is_Overloaded
(Expr
) then
5487 if Has_Good_Profile
(Entity
(Expr
), Report
=> True) then
5488 Subp
:= Entity
(Expr
);
5492 Get_First_Interp
(Expr
, I
, It
);
5493 while Present
(It
.Nam
) loop
5494 if Has_Good_Profile
(It
.Nam
) then
5499 Get_Next_Interp
(I
, It
);
5504 if Present
(Subp
) then
5505 if Is_Abstract_Subprogram
(Subp
) then
5506 Error_Msg_N
("stream subprogram must not be abstract", Expr
);
5509 -- A stream subprogram for an interface type must be a null
5510 -- procedure (RM 13.13.2 (38/3)). Note that the class-wide type
5511 -- of an interface is not an interface type (3.9.4 (6.b/2)).
5513 elsif Is_Interface
(U_Ent
)
5514 and then not Is_Class_Wide_Type
(U_Ent
)
5515 and then not Inside_A_Generic
5517 (Ekind
(Subp
) = E_Function
5521 (Unit_Declaration_Node
(Ultimate_Alias
(Subp
)))))
5524 ("stream subprogram for interface type must be null "
5525 & "procedure", Expr
);
5528 Set_Entity
(Expr
, Subp
);
5529 Set_Etype
(Expr
, Etype
(Subp
));
5531 New_Stream_Subprogram
(N
, U_Ent
, Subp
, TSS_Nam
);
5534 Error_Msg_Name_1
:= Attr
;
5536 if Is_Class_Wide_Type
(Base_Type
(Ent
)) then
5538 ("incorrect expression for class-wide% attribute", Expr
);
5540 Error_Msg_N
("incorrect expression for% attribute", Expr
);
5543 end Analyze_Stream_TSS_Definition
;
5545 ------------------------------
5546 -- Check_Indexing_Functions --
5547 ------------------------------
5549 procedure Check_Indexing_Functions
is
5550 Indexing_Found
: Boolean := False;
5552 procedure Check_Inherited_Indexing
;
5553 -- For a derived type, check that for a derived type, a specification
5554 -- of an indexing aspect can only be confirming, i.e. uses the same
5555 -- name as in the parent type.
5556 -- AI12-0160: Verify that an indexing cannot be specified for
5557 -- a derived type unless it is specified for the parent.
5559 procedure Check_One_Function
(Subp
: Entity_Id
);
5560 -- Check one possible interpretation. Sets Indexing_Found True if a
5561 -- legal indexing function is found.
5563 procedure Illegal_Indexing
(Msg
: String);
5564 -- Diagnose illegal indexing function if not overloaded. In the
5565 -- overloaded case indicate that no legal interpretation exists.
5567 ------------------------------
5568 -- Check_Inherited_Indexing --
5569 ------------------------------
5571 procedure Check_Inherited_Indexing
is
5572 Inherited
: Node_Id
;
5573 Other_Indexing
: Node_Id
;
5576 if Attr
= Name_Constant_Indexing
then
5578 Find_Aspect
(Etype
(Ent
), Aspect_Constant_Indexing
);
5580 Find_Aspect
(Etype
(Ent
), Aspect_Variable_Indexing
);
5582 else pragma Assert
(Attr
= Name_Variable_Indexing
);
5584 Find_Aspect
(Etype
(Ent
), Aspect_Variable_Indexing
);
5586 Find_Aspect
(Etype
(Ent
), Aspect_Constant_Indexing
);
5589 if Present
(Inherited
) then
5590 if Debug_Flag_Dot_XX
then
5593 -- OK if current attribute_definition_clause is expansion of
5594 -- inherited aspect.
5596 elsif Aspect_Rep_Item
(Inherited
) = N
then
5599 -- Check if this is a confirming specification. The name
5600 -- may be overloaded between the parent operation and the
5601 -- inherited one, so we check that the Chars fields match.
5603 elsif Is_Entity_Name
(Expression
(Inherited
))
5604 and then Chars
(Entity
(Expression
(Inherited
))) =
5605 Chars
(Entity
(Expression
(N
)))
5607 Indexing_Found
:= True;
5609 -- Indicate the operation that must be overridden, rather than
5610 -- redefining the indexing aspect.
5614 ("indexing function already inherited from parent type");
5616 ("!override & instead",
5617 N
, Entity
(Expression
(Inherited
)));
5620 -- If not inherited and the parent has another indexing function
5621 -- this is illegal, because it leads to inconsistent results in
5622 -- class-wide calls.
5624 elsif Present
(Other_Indexing
) then
5626 ("cannot specify indexing operation on derived type"
5627 & " if not specified for parent", N
);
5629 end Check_Inherited_Indexing
;
5631 ------------------------
5632 -- Check_One_Function --
5633 ------------------------
5635 procedure Check_One_Function
(Subp
: Entity_Id
) is
5636 Default_Element
: Node_Id
;
5637 Ret_Type
: constant Entity_Id
:= Etype
(Subp
);
5640 if not Is_Overloadable
(Subp
) then
5641 Illegal_Indexing
("illegal indexing function for type&");
5644 elsif Scope
(Subp
) /= Scope
(Ent
) then
5645 if Nkind
(Expr
) = N_Expanded_Name
then
5647 -- Indexing function can't be declared elsewhere
5650 ("indexing function must be declared"
5651 & " in scope of type&");
5654 if Is_Derived_Type
(Ent
) then
5655 Check_Inherited_Indexing
;
5660 elsif No
(First_Formal
(Subp
)) then
5662 ("Indexing requires a function that applies to type&");
5665 elsif No
(Next_Formal
(First_Formal
(Subp
))) then
5667 ("indexing function must have at least two parameters");
5670 elsif Is_Derived_Type
(Ent
) then
5671 Check_Inherited_Indexing
;
5674 if not Check_Primitive_Function
(Subp
) then
5676 ("Indexing aspect requires a function that applies to type&");
5680 -- If partial declaration exists, verify that it is not tagged.
5682 if Ekind
(Current_Scope
) = E_Package
5683 and then Has_Private_Declaration
(Ent
)
5684 and then From_Aspect_Specification
(N
)
5686 List_Containing
(Parent
(Ent
)) =
5687 Private_Declarations
5688 (Specification
(Unit_Declaration_Node
(Current_Scope
)))
5689 and then Nkind
(N
) = N_Attribute_Definition_Clause
5696 First
(Visible_Declarations
5698 (Unit_Declaration_Node
(Current_Scope
))));
5700 while Present
(Decl
) loop
5701 if Nkind
(Decl
) = N_Private_Type_Declaration
5702 and then Ent
= Full_View
(Defining_Identifier
(Decl
))
5703 and then Tagged_Present
(Decl
)
5704 and then No
(Aspect_Specifications
(Decl
))
5707 ("Indexing aspect cannot be specified on full view "
5708 & "if partial view is tagged");
5717 -- An indexing function must return either the default element of
5718 -- the container, or a reference type. For variable indexing it
5719 -- must be the latter.
5722 Find_Value_Of_Aspect
5723 (Etype
(First_Formal
(Subp
)), Aspect_Iterator_Element
);
5725 if Present
(Default_Element
) then
5726 Analyze
(Default_Element
);
5729 -- For variable_indexing the return type must be a reference type
5731 if Attr
= Name_Variable_Indexing
then
5732 if not Has_Implicit_Dereference
(Ret_Type
) then
5734 ("variable indexing must return a reference type");
5737 elsif Is_Access_Constant
5738 (Etype
(First_Discriminant
(Ret_Type
)))
5741 ("variable indexing must return an access to variable");
5746 if Has_Implicit_Dereference
(Ret_Type
)
5749 (Etype
(Get_Reference_Discriminant
(Ret_Type
)))
5752 ("constant indexing must return an access to constant");
5755 elsif Is_Access_Type
(Etype
(First_Formal
(Subp
)))
5756 and then not Is_Access_Constant
(Etype
(First_Formal
(Subp
)))
5759 ("constant indexing must apply to an access to constant");
5764 -- All checks succeeded
5766 Indexing_Found
:= True;
5767 end Check_One_Function
;
5769 -----------------------
5770 -- Illegal_Indexing --
5771 -----------------------
5773 procedure Illegal_Indexing
(Msg
: String) is
5775 Error_Msg_NE
(Msg
, N
, Ent
);
5776 end Illegal_Indexing
;
5778 -- Start of processing for Check_Indexing_Functions
5782 Check_Inherited_Indexing
;
5787 if not Is_Overloaded
(Expr
) then
5788 Check_One_Function
(Entity
(Expr
));
5796 Indexing_Found
:= False;
5797 Get_First_Interp
(Expr
, I
, It
);
5798 while Present
(It
.Nam
) loop
5800 -- Note that analysis will have added the interpretation
5801 -- that corresponds to the dereference. We only check the
5802 -- subprogram itself. Ignore homonyms that may come from
5803 -- derived types in the context.
5805 if Is_Overloadable
(It
.Nam
)
5806 and then Comes_From_Source
(It
.Nam
)
5808 Check_One_Function
(It
.Nam
);
5811 Get_Next_Interp
(I
, It
);
5816 if not Indexing_Found
and then not Error_Posted
(N
) then
5818 ("aspect Indexing requires a local function that applies to "
5819 & "type&", Expr
, Ent
);
5821 end Check_Indexing_Functions
;
5823 ------------------------------
5824 -- Check_Iterator_Functions --
5825 ------------------------------
5827 procedure Check_Iterator_Functions
is
5828 function Valid_Default_Iterator
(Subp
: Entity_Id
) return Boolean;
5829 -- Check one possible interpretation for validity
5831 ----------------------------
5832 -- Valid_Default_Iterator --
5833 ----------------------------
5835 function Valid_Default_Iterator
(Subp
: Entity_Id
) return Boolean is
5836 Root_T
: constant Entity_Id
:= Root_Type
(Etype
(Etype
(Subp
)));
5840 if not Check_Primitive_Function
(Subp
) then
5843 -- The return type must be derived from a type in an instance
5844 -- of Iterator.Interfaces, and thus its root type must have a
5847 elsif Chars
(Root_T
) /= Name_Forward_Iterator
5848 and then Chars
(Root_T
) /= Name_Reversible_Iterator
5853 Formal
:= First_Formal
(Subp
);
5856 -- False if any subsequent formal has no default expression
5858 Next_Formal
(Formal
);
5859 while Present
(Formal
) loop
5860 if No
(Expression
(Parent
(Formal
))) then
5864 Next_Formal
(Formal
);
5867 -- True if all subsequent formals have default expressions
5870 end Valid_Default_Iterator
;
5872 -- Start of processing for Check_Iterator_Functions
5877 if not Is_Entity_Name
(Expr
) then
5878 Error_Msg_N
("aspect Iterator must be a function name", Expr
);
5881 if not Is_Overloaded
(Expr
) then
5882 if Entity
(Expr
) /= Any_Id
5883 and then not Check_Primitive_Function
(Entity
(Expr
))
5886 ("aspect Indexing requires a function that applies to type&",
5887 Entity
(Expr
), Ent
);
5890 -- Flag the default_iterator as well as the denoted function.
5892 if not Valid_Default_Iterator
(Entity
(Expr
)) then
5893 Error_Msg_N
("improper function for default iterator!", Expr
);
5898 Default
: Entity_Id
:= Empty
;
5903 Get_First_Interp
(Expr
, I
, It
);
5904 while Present
(It
.Nam
) loop
5905 if not Check_Primitive_Function
(It
.Nam
)
5906 or else not Valid_Default_Iterator
(It
.Nam
)
5910 elsif Present
(Default
) then
5912 -- An explicit one should override an implicit one
5914 if Comes_From_Source
(Default
) =
5915 Comes_From_Source
(It
.Nam
)
5917 Error_Msg_N
("default iterator must be unique", Expr
);
5918 Error_Msg_Sloc
:= Sloc
(Default
);
5919 Error_Msg_N
("\\possible interpretation#", Expr
);
5920 Error_Msg_Sloc
:= Sloc
(It
.Nam
);
5921 Error_Msg_N
("\\possible interpretation#", Expr
);
5923 elsif Comes_From_Source
(It
.Nam
) then
5930 Get_Next_Interp
(I
, It
);
5933 if Present
(Default
) then
5934 Set_Entity
(Expr
, Default
);
5935 Set_Is_Overloaded
(Expr
, False);
5938 ("no interpretation is a valid default iterator!", Expr
);
5942 end Check_Iterator_Functions
;
5944 -------------------------------
5945 -- Check_Primitive_Function --
5946 -------------------------------
5948 function Check_Primitive_Function
(Subp
: Entity_Id
) return Boolean is
5952 if Ekind
(Subp
) /= E_Function
then
5956 if No
(First_Formal
(Subp
)) then
5959 Ctrl
:= Etype
(First_Formal
(Subp
));
5962 -- To be a primitive operation subprogram has to be in same scope.
5964 if Scope
(Ctrl
) /= Scope
(Subp
) then
5968 -- Type of formal may be the class-wide type, an access to such,
5969 -- or an incomplete view.
5972 or else Ctrl
= Class_Wide_Type
(Ent
)
5974 (Ekind
(Ctrl
) = E_Anonymous_Access_Type
5975 and then (Designated_Type
(Ctrl
) = Ent
5977 Designated_Type
(Ctrl
) = Class_Wide_Type
(Ent
)))
5979 (Ekind
(Ctrl
) = E_Incomplete_Type
5980 and then Full_View
(Ctrl
) = Ent
)
5988 end Check_Primitive_Function
;
5990 ----------------------
5991 -- Duplicate_Clause --
5992 ----------------------
5994 function Duplicate_Clause
return Boolean is
5996 function Check_One_Attr
(Attr_1
, Attr_2
: Name_Id
) return Boolean;
5997 -- Check for one attribute; Attr_1 is the attribute_designator we are
5998 -- looking for. Attr_2 is the attribute_designator of the current
5999 -- node. Normally, this is called just once by Duplicate_Clause, with
6000 -- Attr_1 = Attr_2. However, it needs to be called twice for Size and
6001 -- Value_Size, because these mean the same thing. For compatibility,
6002 -- we allow specifying both Size and Value_Size, but only if the two
6005 --------------------
6006 -- Check_One_Attr --
6007 --------------------
6009 function Check_One_Attr
(Attr_1
, Attr_2
: Name_Id
) return Boolean is
6010 A
: constant Node_Id
:=
6011 Get_Rep_Item
(U_Ent
, Attr_1
, Check_Parents
=> False);
6014 if Attr_1
= Attr_2
then
6015 Error_Msg_Name_1
:= Attr_1
;
6016 Error_Msg_Sloc
:= Sloc
(A
);
6017 Error_Msg_NE
("aspect% for & previously given#", N
, U_Ent
);
6020 pragma Assert
(Attr_1
in Name_Size | Name_Value_Size
);
6021 pragma Assert
(Attr_2
in Name_Size | Name_Value_Size
);
6023 Error_Msg_Name_1
:= Attr_2
;
6024 Error_Msg_Name_2
:= Attr_1
;
6025 Error_Msg_Sloc
:= Sloc
(A
);
6026 Error_Msg_NE
("?% for & conflicts with % #", N
, U_Ent
);
6035 -- Start of processing for Duplicate_Clause
6038 -- Nothing to do if this attribute definition clause comes from
6039 -- an aspect specification, since we could not be duplicating an
6040 -- explicit clause, and we dealt with the case of duplicated aspects
6041 -- in Analyze_Aspect_Specifications.
6043 if From_Aspect_Specification
(N
) then
6047 -- Special cases for Size and Value_Size
6049 if (Chars
(N
) = Name_Size
6050 and then Check_One_Attr
(Name_Value_Size
, Name_Size
))
6052 (Chars
(N
) = Name_Value_Size
6053 and then Check_One_Attr
(Name_Size
, Name_Value_Size
))
6058 -- Normal case (including Size and Value_Size)
6060 return Check_One_Attr
(Chars
(N
), Chars
(N
));
6061 end Duplicate_Clause
;
6063 -- Start of processing for Analyze_Attribute_Definition_Clause
6066 -- The following code is a defense against recursion. Not clear that
6067 -- this can happen legitimately, but perhaps some error situations can
6068 -- cause it, and we did see this recursion during testing.
6070 if Analyzed
(N
) then
6073 Set_Analyzed
(N
, True);
6076 Check_Restriction_No_Use_Of_Attribute
(N
);
6078 if Is_Aspect_Id
(Chars
(N
)) then
6079 -- 6.1/3 No_Specification_of_Aspect: Identifies an aspect for which
6080 -- no aspect_specification, attribute_definition_clause, or pragma
6082 Check_Restriction_No_Specification_Of_Aspect
(N
);
6085 -- Ignore some selected attributes in CodePeer mode since they are not
6086 -- relevant in this context.
6088 if CodePeer_Mode
then
6091 -- Ignore Component_Size in CodePeer mode, to avoid changing the
6092 -- internal representation of types by implicitly packing them.
6094 when Attribute_Component_Size
=>
6095 Rewrite
(N
, Make_Null_Statement
(Sloc
(N
)));
6103 -- Process Ignore_Rep_Clauses option
6105 if Ignore_Rep_Clauses
then
6108 -- The following should be ignored. They do not affect legality
6109 -- and may be target dependent. The basic idea of -gnatI is to
6110 -- ignore any rep clauses that may be target dependent but do not
6111 -- affect legality (except possibly to be rejected because they
6112 -- are incompatible with the compilation target).
6114 when Attribute_Alignment
6115 | Attribute_Bit_Order
6116 | Attribute_Component_Size
6117 | Attribute_Default_Scalar_Storage_Order
6118 | Attribute_Machine_Radix
6119 | Attribute_Object_Size
6120 | Attribute_Scalar_Storage_Order
6123 | Attribute_Stream_Size
6124 | Attribute_Value_Size
6126 Kill_Rep_Clause
(N
);
6129 -- The following should not be ignored, because in the first place
6130 -- they are reasonably portable, and should not cause problems
6131 -- in compiling code from another target, and also they do affect
6132 -- legality, e.g. failing to provide a stream attribute for a type
6133 -- may make a program illegal.
6135 when Attribute_External_Tag
6138 | Attribute_Put_Image
6140 | Attribute_Simple_Storage_Pool
6141 | Attribute_Storage_Pool
6142 | Attribute_Storage_Size
6147 -- We do not do anything here with address clauses, they will be
6148 -- removed by Freeze later on, but for now, it works better to
6149 -- keep them in the tree.
6151 when Attribute_Address
=>
6154 -- Other cases are errors ("attribute& cannot be set with
6155 -- definition clause"), which will be caught below.
6163 Ent
:= Entity
(Nam
);
6165 if Rep_Item_Too_Early
(Ent
, N
) then
6169 -- Rep clause applies to (underlying) full view of private or incomplete
6170 -- type if we have one (if not, this is a premature use of the type).
6171 -- However, some semantic checks need to be done on the specified entity
6172 -- i.e. the private view, so we save it in Ent.
6174 if Is_Private_Type
(Ent
)
6175 and then Is_Derived_Type
(Ent
)
6176 and then not Is_Tagged_Type
(Ent
)
6177 and then No
(Full_View
(Ent
))
6178 and then No
(Underlying_Full_View
(Ent
))
6182 elsif Ekind
(Ent
) = E_Incomplete_Type
then
6184 -- The attribute applies to the full view, set the entity of the
6185 -- attribute definition accordingly.
6187 Ent
:= Underlying_Type
(Ent
);
6189 Set_Entity
(Nam
, Ent
);
6192 U_Ent
:= Underlying_Type
(Ent
);
6195 -- Avoid cascaded error
6197 if Etype
(Nam
) = Any_Type
then
6200 -- Must be declared in current scope or in case of an aspect
6201 -- specification, must be visible in current scope.
6203 elsif Scope
(Ent
) /= Current_Scope
6205 not (From_Aspect_Specification
(N
)
6206 and then Scope_Within_Or_Same
(Current_Scope
, Scope
(Ent
)))
6208 Error_Msg_N
("entity must be declared in this scope", Nam
);
6211 -- Must not be a source renaming (we do have some cases where the
6212 -- expander generates a renaming, and those cases are OK, in such
6213 -- cases any attribute applies to the renamed object as well).
6215 elsif Is_Object
(Ent
)
6216 and then Present
(Renamed_Object
(Ent
))
6218 -- In the case of a renamed object from source, this is an error
6219 -- unless the object is an aggregate and the renaming is created
6220 -- for an object declaration.
6222 if Comes_From_Source
(Renamed_Object
(Ent
))
6223 and then Nkind
(Renamed_Object
(Ent
)) /= N_Aggregate
6225 Get_Name_String
(Chars
(N
));
6226 Error_Msg_Strlen
:= Name_Len
;
6227 Error_Msg_String
(1 .. Name_Len
) := Name_Buffer
(1 .. Name_Len
);
6229 ("~ clause not allowed for a renaming declaration "
6230 & "(RM 13.1(6))", Nam
);
6233 -- For the case of a compiler generated renaming, the attribute
6234 -- definition clause applies to the renamed object created by the
6235 -- expander. The easiest general way to handle this is to create a
6236 -- copy of the attribute definition clause for this object.
6238 elsif Is_Entity_Name
(Renamed_Object
(Ent
)) then
6240 Make_Attribute_Definition_Clause
(Loc
,
6242 New_Occurrence_Of
(Entity
(Renamed_Object
(Ent
)), Loc
),
6244 Expression
=> Duplicate_Subexpr
(Expression
(N
))));
6246 -- If the renamed object is not an entity, it must be a dereference
6247 -- of an unconstrained function call, and we must introduce a new
6248 -- declaration to capture the expression. This is needed in the case
6249 -- of 'Alignment, where the original declaration must be rewritten.
6253 (Nkind
(Renamed_Object
(Ent
)) = N_Explicit_Dereference
);
6257 -- If no underlying entity, use entity itself, applies to some
6258 -- previously detected error cases ???
6260 elsif No
(U_Ent
) then
6263 -- Cannot specify for a subtype (exception Object/Value_Size)
6265 elsif Is_Type
(U_Ent
)
6266 and then not Is_First_Subtype
(U_Ent
)
6267 and then Id
/= Attribute_Object_Size
6268 and then Id
/= Attribute_Value_Size
6269 and then not From_At_Mod
(N
)
6271 Error_Msg_N
("cannot specify attribute for subtype", Nam
);
6275 Set_Entity
(N
, U_Ent
);
6277 -- Switch on particular attribute
6285 -- Address attribute definition clause
6287 when Attribute_Address
=> Address
: begin
6289 -- A little error check, catch for X'Address use X'Address;
6291 if Nkind
(Nam
) = N_Identifier
6292 and then Nkind
(Expr
) = N_Attribute_Reference
6293 and then Attribute_Name
(Expr
) = Name_Address
6294 and then Nkind
(Prefix
(Expr
)) = N_Identifier
6295 and then Chars
(Nam
) = Chars
(Prefix
(Expr
))
6298 ("address for & is self-referencing", Prefix
(Expr
), Ent
);
6302 -- Not that special case, carry on with analysis of expression
6304 Analyze_And_Resolve
(Expr
, RTE
(RE_Address
));
6306 -- Even when ignoring rep clauses we need to indicate that the
6307 -- entity has an address clause and thus it is legal to declare
6308 -- it imported. Freeze will get rid of the address clause later.
6309 -- Also call Set_Address_Taken to indicate that an address clause
6310 -- was present, even if we are about to remove it.
6312 if Ignore_Rep_Clauses
then
6313 Set_Address_Taken
(U_Ent
);
6315 if Ekind
(U_Ent
) in E_Variable | E_Constant
then
6316 Record_Rep_Item
(U_Ent
, N
);
6322 if Duplicate_Clause
then
6325 -- Case of address clause for subprogram
6327 elsif Is_Subprogram
(U_Ent
) then
6328 if Has_Homonym
(U_Ent
) then
6330 ("address clause cannot be given for overloaded "
6331 & "subprogram", Nam
);
6335 -- For subprograms, all address clauses are permitted, and we
6336 -- mark the subprogram as having a deferred freeze so that Gigi
6337 -- will not elaborate it too soon.
6339 -- Above needs more comments, what is too soon about???
6341 Set_Has_Delayed_Freeze
(U_Ent
);
6343 -- Case of address clause for entry
6345 elsif Ekind
(U_Ent
) = E_Entry
then
6346 if Nkind
(Parent
(N
)) = N_Task_Body
then
6348 ("entry address must be specified in task spec", Nam
);
6352 -- For entries, we require a constant address
6354 Check_Constant_Address_Clause
(Expr
, U_Ent
);
6356 -- Special checks for task types
6358 if Is_Task_Type
(Scope
(U_Ent
))
6359 and then Comes_From_Source
(Scope
(U_Ent
))
6362 ("??entry address declared for entry in task type", N
);
6364 ("\??only one task can be declared of this type", N
);
6367 -- Entry address clauses are obsolescent
6369 Check_Restriction
(No_Obsolescent_Features
, N
);
6371 if Warn_On_Obsolescent_Feature
then
6373 ("?j?attaching interrupt to task entry is an obsolescent "
6374 & "feature (RM J.7.1)", N
);
6376 ("\?j?use interrupt procedure instead", N
);
6379 -- Case of address clause for an object
6381 elsif Ekind
(U_Ent
) in E_Constant | E_Variable
then
6383 -- Disallow case of an address clause for an object of an
6384 -- indefinite subtype which takes its bounds/discriminant/tag
6385 -- from its initial value. Without this, we get a Gigi
6386 -- assertion failure for things like
6387 -- X : String := Some_Function (...) with Address => ...;
6388 -- where the result subtype of the function is unconstrained.
6390 -- We want to reject two cases: the class-wide case, and the
6391 -- case where the FE conjures up a renaming declaration and
6392 -- would then otherwise generate an address specification for
6393 -- that renaming (which is a malformed tree, which is why Gigi
6396 if Is_Class_Wide_Type
(Etype
(U_Ent
)) then
6398 ("address specification not supported for class-wide " &
6399 "object declaration", Nam
);
6401 elsif Is_Constr_Subt_For_U_Nominal
(Etype
(U_Ent
))
6403 Nkind
(Parent
(U_Ent
)) = N_Object_Renaming_Declaration
6405 -- Confirm accuracy of " and dynamic size" message text
6406 -- before including it. We want to include that text when
6407 -- it is correct because it may be useful to the reader.
6408 -- The case where we omit that part of the message text
6409 -- might be dead code, but let's not rely on that.
6412 ("address specification not supported for object " &
6413 "declaration with indefinite nominal subtype" &
6414 (if Size_Known_At_Compile_Time
(Etype
(U_Ent
))
6416 else " and dynamic size"), Nam
);
6421 Expr
: constant Node_Id
:= Expression
(N
);
6426 -- Exported variables cannot have an address clause, because
6427 -- this cancels the effect of the pragma Export.
6429 if Is_Exported
(U_Ent
) then
6431 ("cannot export object with address clause", Nam
);
6435 Find_Overlaid_Entity
(N
, O_Ent
, Off
);
6437 if Present
(O_Ent
) then
6439 -- If the object overlays a constant object, mark it so
6441 if Is_Constant_Object
(O_Ent
) then
6442 Set_Overlays_Constant
(U_Ent
);
6445 -- If the address clause is of the form:
6447 -- for X'Address use Y'Address;
6451 -- C : constant Address := Y'Address;
6453 -- for X'Address use C;
6455 -- then we make an entry in the table to check the size
6456 -- and alignment of the overlaying variable. But we defer
6457 -- this check till after code generation to take full
6458 -- advantage of the annotation done by the back end.
6460 -- If the entity has a generic type, the check will be
6461 -- performed in the instance if the actual type justifies
6462 -- it, and we do not insert the clause in the table to
6463 -- prevent spurious warnings.
6465 -- Note: we used to test Comes_From_Source and only give
6466 -- this warning for source entities, but we have removed
6467 -- this test. It really seems bogus to generate overlays
6468 -- that would trigger this warning in generated code.
6469 -- Furthermore, by removing the test, we handle the
6470 -- aspect case properly.
6472 if Is_Object
(O_Ent
)
6473 and then not Is_Generic_Formal
(O_Ent
)
6474 and then not Is_Generic_Type
(Etype
(U_Ent
))
6475 and then Address_Clause_Overlay_Warnings
6477 Register_Address_Clause_Check
6478 (N
, U_Ent
, No_Uint
, O_Ent
, Off
);
6481 -- If the overlay changes the storage order, warn since
6482 -- the construct is not really supported by the back end.
6483 -- Also mark the entity as being volatile to block the
6484 -- optimizer, even if there is no warranty on the result.
6486 if (Is_Record_Type
(Etype
(U_Ent
))
6487 or else Is_Array_Type
(Etype
(U_Ent
)))
6488 and then (Is_Record_Type
(Etype
(O_Ent
))
6489 or else Is_Array_Type
(Etype
(O_Ent
)))
6490 and then Reverse_Storage_Order
(Etype
(U_Ent
)) /=
6491 Reverse_Storage_Order
(Etype
(O_Ent
))
6494 ("??overlay changes scalar storage order", Expr
);
6495 Set_Treat_As_Volatile
(U_Ent
);
6499 -- If this is not an overlay, mark a variable as being
6500 -- volatile to prevent unwanted optimizations. It's a
6501 -- conservative interpretation of RM 13.3(19) for the
6502 -- cases where the compiler cannot detect potential
6503 -- aliasing issues easily and it also covers the case
6504 -- of an absolute address where the volatile aspect is
6505 -- kind of implicit.
6507 if Ekind
(U_Ent
) = E_Variable
then
6508 Set_Treat_As_Volatile
(U_Ent
);
6511 -- Make an entry in the table for an absolute address as
6512 -- above to check that the value is compatible with the
6513 -- alignment of the object.
6516 Addr
: constant Node_Id
:= Address_Value
(Expr
);
6518 if Compile_Time_Known_Value
(Addr
)
6519 and then Address_Clause_Overlay_Warnings
6521 Register_Address_Clause_Check
6522 (N
, U_Ent
, Expr_Value
(Addr
), Empty
, False);
6527 -- Issue an unconditional warning for a constant overlaying
6528 -- a variable. For the reverse case, we will issue it only
6529 -- if the variable is modified.
6530 -- Within a generic unit an In_Parameter is a constant.
6531 -- It can be instantiated with a variable, in which case
6532 -- there will be a warning on the instance.
6534 if Ekind
(U_Ent
) = E_Constant
6535 and then Present
(O_Ent
)
6536 and then Ekind
(O_Ent
) /= E_Generic_In_Parameter
6537 and then not Overlays_Constant
(U_Ent
)
6538 and then Address_Clause_Overlay_Warnings
6540 Error_Msg_N
("?o?constant overlays a variable", Expr
);
6542 -- Imported variables can have an address clause, but then
6543 -- the import is pretty meaningless except to suppress
6544 -- initializations, so we do not need such variables to
6545 -- be statically allocated (and in fact it causes trouble
6546 -- if the address clause is a local value).
6548 elsif Is_Imported
(U_Ent
) then
6549 Set_Is_Statically_Allocated
(U_Ent
, False);
6552 -- We mark a possible modification of a variable with an
6553 -- address clause, since it is likely aliasing is occurring.
6555 Note_Possible_Modification
(Nam
, Sure
=> False);
6557 -- Legality checks on the address clause for initialized
6558 -- objects is deferred until the freeze point, because
6559 -- a subsequent pragma might indicate that the object
6560 -- is imported and thus not initialized. Also, the address
6561 -- clause might involve entities that have yet to be
6564 Set_Has_Delayed_Freeze
(U_Ent
);
6566 -- If an initialization call has been generated for this
6567 -- object, it needs to be deferred to after the freeze node
6568 -- we have just now added, otherwise GIGI will see a
6569 -- reference to the variable (as actual to the IP call)
6570 -- before its definition.
6573 Init_Call
: constant Node_Id
:=
6574 Remove_Init_Call
(U_Ent
, N
);
6577 if Present
(Init_Call
) then
6578 Append_Freeze_Action
(U_Ent
, Init_Call
);
6580 -- Reset Initialization_Statements pointer so that
6581 -- if there is a pragma Import further down, it can
6582 -- clear any default initialization.
6584 Set_Initialization_Statements
(U_Ent
, Init_Call
);
6588 -- Entity has delayed freeze, so we will generate an
6589 -- alignment check at the freeze point unless suppressed.
6591 if not Range_Checks_Suppressed
(U_Ent
)
6592 and then not Alignment_Checks_Suppressed
(U_Ent
)
6594 Set_Check_Address_Alignment
(N
);
6597 -- Kill the size check code, since we are not allocating
6598 -- the variable, it is somewhere else.
6600 Kill_Size_Check_Code
(U_Ent
);
6603 -- Not a valid entity for an address clause
6606 Error_Msg_N
("address cannot be given for &", Nam
);
6614 -- Alignment attribute definition clause
6616 when Attribute_Alignment
=> Alignment
: declare
6617 Align
: constant Uint
:= Get_Alignment_Value
(Expr
);
6618 Max_Align
: constant Uint
:= UI_From_Int
(Maximum_Alignment
);
6623 if not Is_Type
(U_Ent
)
6624 and then Ekind
(U_Ent
) /= E_Variable
6625 and then Ekind
(U_Ent
) /= E_Constant
6627 Error_Msg_N
("alignment cannot be given for &", Nam
);
6629 elsif Duplicate_Clause
then
6632 elsif Present
(Align
) then
6633 Set_Has_Alignment_Clause
(U_Ent
);
6635 -- Tagged type case, check for attempt to set alignment to a
6636 -- value greater than Max_Align, and reset if so.
6638 if Is_Tagged_Type
(U_Ent
) and then Align
> Max_Align
then
6640 ("alignment for & set to Maximum_Aligment??", Nam
);
6641 Set_Alignment
(U_Ent
, Max_Align
);
6646 Set_Alignment
(U_Ent
, Align
);
6649 -- For an array type, U_Ent is the first subtype. In that case,
6650 -- also set the alignment of the anonymous base type so that
6651 -- other subtypes (such as the itypes for aggregates of the
6652 -- type) also receive the expected alignment.
6654 if Is_Array_Type
(U_Ent
) then
6655 Set_Alignment
(Base_Type
(U_Ent
), Align
);
6664 -- Bit_Order attribute definition clause
6666 when Attribute_Bit_Order
=>
6667 if not Is_Record_Type
(U_Ent
) then
6669 ("Bit_Order can only be defined for record type", Nam
);
6671 elsif Is_Tagged_Type
(U_Ent
) and then Is_Derived_Type
(U_Ent
) then
6673 ("Bit_Order cannot be defined for record extensions", Nam
);
6675 elsif Duplicate_Clause
then
6679 Analyze_And_Resolve
(Expr
, RTE
(RE_Bit_Order
));
6681 if Etype
(Expr
) = Any_Type
then
6684 elsif not Is_OK_Static_Expression
(Expr
) then
6685 Flag_Non_Static_Expr
6686 ("Bit_Order requires static expression!", Expr
);
6688 elsif (Expr_Value
(Expr
) = 0) /= Bytes_Big_Endian
then
6689 Set_Reverse_Bit_Order
(Base_Type
(U_Ent
), True);
6693 --------------------
6694 -- Component_Size --
6695 --------------------
6697 -- Component_Size attribute definition clause
6699 when Attribute_Component_Size
=> Component_Size_Case
: declare
6700 Csize
: constant Uint
:= Static_Integer
(Expr
);
6704 New_Ctyp
: Entity_Id
;
6708 if not Is_Array_Type
(U_Ent
) then
6709 Error_Msg_N
("component size requires array type", Nam
);
6713 Btype
:= Base_Type
(U_Ent
);
6714 Ctyp
:= Component_Type
(Btype
);
6716 if Duplicate_Clause
then
6719 elsif Rep_Item_Too_Early
(Btype
, N
) then
6722 elsif Present
(Csize
) then
6723 Check_Size
(Expr
, Ctyp
, Csize
, Biased
);
6725 -- For the biased case, build a declaration for a subtype that
6726 -- will be used to represent the biased subtype that reflects
6727 -- the biased representation of components. We need the subtype
6728 -- to get proper conversions on referencing elements of the
6733 Make_Defining_Identifier
(Loc
,
6735 New_External_Name
(Chars
(U_Ent
), 'C', 0, 'T'));
6738 Make_Subtype_Declaration
(Loc
,
6739 Defining_Identifier
=> New_Ctyp
,
6740 Subtype_Indication
=>
6741 New_Occurrence_Of
(Component_Type
(Btype
), Loc
));
6743 Set_Parent
(Decl
, N
);
6744 Analyze
(Decl
, Suppress
=> All_Checks
);
6746 Set_Has_Delayed_Freeze
(New_Ctyp
, False);
6747 Reinit_Esize
(New_Ctyp
);
6748 Set_RM_Size
(New_Ctyp
, Csize
);
6749 Reinit_Alignment
(New_Ctyp
);
6750 Set_Is_Itype
(New_Ctyp
, True);
6751 Set_Associated_Node_For_Itype
(New_Ctyp
, U_Ent
);
6753 Set_Component_Type
(Btype
, New_Ctyp
);
6754 Set_Biased
(New_Ctyp
, N
, "component size clause");
6757 Set_Component_Size
(Btype
, Csize
);
6759 -- Deal with warning on overridden size
6761 if Warn_On_Overridden_Size
6762 and then Has_Size_Clause
(Ctyp
)
6763 and then RM_Size
(Ctyp
) /= Csize
6766 ("component size overrides size clause for&?.s?", N
, Ctyp
);
6769 Set_Has_Component_Size_Clause
(Btype
, True);
6770 Set_Has_Non_Standard_Rep
(Btype
, True);
6772 end Component_Size_Case
;
6774 -----------------------
6775 -- Constant_Indexing --
6776 -----------------------
6778 when Attribute_Constant_Indexing
=>
6779 Check_Indexing_Functions
;
6785 when Attribute_CPU
=>
6786 pragma Assert
(From_Aspect_Specification
(N
));
6787 -- The parser forbids this clause in source code, so it must have
6788 -- come from an aspect specification.
6790 if not Is_Task_Type
(U_Ent
) then
6791 Error_Msg_N
("'C'P'U can only be defined for task", Nam
);
6793 elsif Duplicate_Clause
then
6797 -- The expression must be analyzed in the special manner
6798 -- described in "Handling of Default and Per-Object
6799 -- Expressions" in sem.ads.
6801 -- The visibility to the components must be established
6802 -- and restored before and after analysis.
6805 Preanalyze_Spec_Expression
(Expr
, RTE
(RE_CPU_Range
));
6808 -- AI12-0117-1, "Restriction No_Tasks_Unassigned_To_CPU":
6809 -- If the expression is static, and its value is
6810 -- System.Multiprocessors.Not_A_Specific_CPU (i.e. zero) then
6811 -- that's a violation of No_Tasks_Unassigned_To_CPU. It might
6812 -- seem better to refer to Not_A_Specific_CPU here, but that
6813 -- involves a lot of horsing around with Rtsfind, and this
6814 -- value is not going to change, so it's better to hardwire
6817 -- AI12-0055-1, "All properties of a usage profile are defined
6818 -- by pragmas": If the expression is nonstatic, that's a
6819 -- violation of No_Dynamic_CPU_Assignment.
6821 if Is_OK_Static_Expression
(Expr
) then
6822 if Expr_Value
(Expr
) = Uint_0
then
6823 Check_Restriction
(No_Tasks_Unassigned_To_CPU
, Expr
);
6826 Check_Restriction
(No_Dynamic_CPU_Assignment
, Expr
);
6830 ----------------------
6831 -- Default_Iterator --
6832 ----------------------
6834 when Attribute_Default_Iterator
=> Default_Iterator
: declare
6839 -- If target type is untagged, further checks are irrelevant
6841 if not Is_Tagged_Type
(U_Ent
) then
6843 ("aspect Default_Iterator applies to tagged type", Nam
);
6847 Check_Iterator_Functions
;
6851 if not Is_Entity_Name
(Expr
)
6852 or else Ekind
(Entity
(Expr
)) /= E_Function
6854 Error_Msg_N
("aspect Iterator must be a function", Expr
);
6857 Func
:= Entity
(Expr
);
6860 -- The type of the first parameter must be T, T'class, or a
6861 -- corresponding access type (5.5.1 (8/3). If function is
6862 -- parameterless label type accordingly.
6864 if No
(First_Formal
(Func
)) then
6867 Typ
:= Etype
(First_Formal
(Func
));
6871 or else Typ
= Class_Wide_Type
(U_Ent
)
6872 or else (Is_Access_Type
(Typ
)
6873 and then Designated_Type
(Typ
) = U_Ent
)
6874 or else (Is_Access_Type
(Typ
)
6875 and then Designated_Type
(Typ
) =
6876 Class_Wide_Type
(U_Ent
))
6882 ("Default_Iterator must be a primitive of&", Func
, U_Ent
);
6884 end Default_Iterator
;
6886 ------------------------
6887 -- Dispatching_Domain --
6888 ------------------------
6890 when Attribute_Dispatching_Domain
=>
6891 pragma Assert
(From_Aspect_Specification
(N
));
6892 -- The parser forbids this clause in source code, so it must have
6893 -- come from an aspect specification.
6895 if not Is_Task_Type
(U_Ent
) then
6897 ("Dispatching_Domain can only be defined for task", Nam
);
6899 elsif Duplicate_Clause
then
6903 -- The expression must be analyzed in the special manner
6904 -- described in "Handling of Default and Per-Object
6905 -- Expressions" in sem.ads.
6907 -- The visibility to the components must be restored
6911 Preanalyze_Spec_Expression
6912 (Expr
, RTE
(RE_Dispatching_Domain
));
6921 when Attribute_External_Tag
=>
6922 if not Is_Tagged_Type
(U_Ent
) then
6923 Error_Msg_N
("should be a tagged type", Nam
);
6926 if Duplicate_Clause
then
6930 Analyze_And_Resolve
(Expr
, Standard_String
);
6932 if not Is_OK_Static_Expression
(Expr
) then
6933 Flag_Non_Static_Expr
6934 ("static string required for tag name!", Nam
);
6937 if not Is_Library_Level_Entity
(U_Ent
) then
6939 ("??non-unique external tag supplied for &", N
, U_Ent
);
6941 ("\??same external tag applies to all subprogram calls",
6944 ("\??corresponding internal tag cannot be obtained", N
);
6948 --------------------------
6949 -- Implicit_Dereference --
6950 --------------------------
6952 when Attribute_Implicit_Dereference
=>
6954 -- Legality checks already performed at the point of the type
6955 -- declaration, aspect is not delayed.
6963 when Attribute_Input
=>
6964 Analyze_Stream_TSS_Definition
(TSS_Stream_Input
);
6965 Set_Has_Specified_Stream_Input
(Ent
);
6967 ------------------------
6968 -- Interrupt_Priority --
6969 ------------------------
6971 when Attribute_Interrupt_Priority
=>
6972 pragma Assert
(From_Aspect_Specification
(N
));
6973 -- The parser forbids this clause in source code, so it must have
6974 -- come from an aspect specification.
6976 if not Is_Concurrent_Type
(U_Ent
) then
6978 ("Interrupt_Priority can only be defined for task and "
6979 & "protected object", Nam
);
6981 elsif Duplicate_Clause
then
6985 -- The expression must be analyzed in the special manner
6986 -- described in "Handling of Default and Per-Object
6987 -- Expressions" in sem.ads.
6989 -- The visibility to the components must be restored
6993 Preanalyze_Spec_Expression
6994 (Expr
, RTE
(RE_Interrupt_Priority
));
6998 -- Check the No_Task_At_Interrupt_Priority restriction
7000 if Is_Task_Type
(U_Ent
) then
7001 Check_Restriction
(No_Task_At_Interrupt_Priority
, N
);
7009 when Attribute_Iterable
=>
7012 if Nkind
(Expr
) /= N_Aggregate
then
7013 Error_Msg_N
("aspect Iterable must be an aggregate", Expr
);
7021 Assoc
:= First
(Component_Associations
(Expr
));
7022 while Present
(Assoc
) loop
7023 Analyze
(Expression
(Assoc
));
7025 if not Is_Entity_Name
(Expression
(Assoc
))
7026 or else Ekind
(Entity
(Expression
(Assoc
))) /= E_Function
7028 Error_Msg_N
("value must be a function", Assoc
);
7035 ----------------------
7036 -- Iterator_Element --
7037 ----------------------
7039 when Attribute_Iterator_Element
=>
7042 if not Is_Entity_Name
(Expr
)
7043 or else not Is_Type
(Entity
(Expr
))
7045 Error_Msg_N
("aspect Iterator_Element must be a type", Expr
);
7053 -- Machine radix attribute definition clause
7055 when Attribute_Machine_Radix
=> Machine_Radix
: declare
7056 Radix
: constant Uint
:= Static_Integer
(Expr
);
7059 if not Is_Decimal_Fixed_Point_Type
(U_Ent
) then
7060 Error_Msg_N
("decimal fixed-point type expected for &", Nam
);
7062 elsif Duplicate_Clause
then
7065 elsif Present
(Radix
) then
7066 Set_Has_Machine_Radix_Clause
(U_Ent
);
7067 Set_Has_Non_Standard_Rep
(Base_Type
(U_Ent
));
7072 elsif Radix
= 10 then
7073 Set_Machine_Radix_10
(U_Ent
);
7076 Error_Msg_N
("machine radix value must be 2 or 10", Expr
);
7085 -- Object_Size attribute definition clause
7087 when Attribute_Object_Size
=> Object_Size
: declare
7088 Size
: constant Uint
:= Static_Integer
(Expr
);
7091 pragma Warnings
(Off
, Biased
);
7094 if not Is_Type
(U_Ent
) then
7095 Error_Msg_N
("Object_Size cannot be given for &", Nam
);
7097 elsif Duplicate_Clause
then
7101 Check_Size
(Expr
, U_Ent
, Size
, Biased
);
7103 if No
(Size
) or else Size
<= 0 then
7104 Error_Msg_N
("Object_Size must be positive", Expr
);
7106 elsif Is_Scalar_Type
(U_Ent
) then
7107 if Size
/= 8 and then Size
/= 16 and then Size
/= 32
7108 and then UI_Mod
(Size
, 64) /= 0
7111 ("Object_Size must be 8, 16, 32, or multiple of 64",
7115 elsif Size
mod 8 /= 0 then
7116 Error_Msg_N
("Object_Size must be a multiple of 8", Expr
);
7119 Set_Esize
(U_Ent
, Size
);
7120 Set_Has_Object_Size_Clause
(U_Ent
);
7121 Alignment_Check_For_Size_Change
(U_Ent
, Size
);
7129 when Attribute_Output
=>
7130 Analyze_Stream_TSS_Definition
(TSS_Stream_Output
);
7131 Set_Has_Specified_Stream_Output
(Ent
);
7137 when Attribute_Priority
=>
7139 -- Priority attribute definition clause not allowed except from
7140 -- aspect specification.
7142 if From_Aspect_Specification
(N
) then
7143 if not (Is_Concurrent_Type
(U_Ent
)
7144 or else Ekind
(U_Ent
) = E_Procedure
)
7147 ("Priority can only be defined for task and protected "
7150 elsif Duplicate_Clause
then
7154 -- The expression must be analyzed in the special manner
7155 -- described in "Handling of Default and Per-Object
7156 -- Expressions" in sem.ads.
7158 -- The visibility to the components must be restored
7161 Preanalyze_Spec_Expression
(Expr
, Standard_Integer
);
7164 if not Is_OK_Static_Expression
(Expr
) then
7165 Check_Restriction
(Static_Priorities
, Expr
);
7171 ("attribute& cannot be set with definition clause", N
);
7178 when Attribute_Put_Image
=>
7179 Analyze_Put_Image_TSS_Definition
;
7185 when Attribute_Read
=>
7186 Analyze_Stream_TSS_Definition
(TSS_Stream_Read
);
7187 Set_Has_Specified_Stream_Read
(Ent
);
7189 --------------------------
7190 -- Scalar_Storage_Order --
7191 --------------------------
7193 -- Scalar_Storage_Order attribute definition clause
7195 when Attribute_Scalar_Storage_Order
=>
7196 if not (Is_Record_Type
(U_Ent
) or else Is_Array_Type
(U_Ent
)) then
7198 ("Scalar_Storage_Order can only be defined for record or "
7199 & "array type", Nam
);
7201 elsif Duplicate_Clause
then
7205 Analyze_And_Resolve
(Expr
, RTE
(RE_Bit_Order
));
7207 if Etype
(Expr
) = Any_Type
then
7210 elsif not Is_OK_Static_Expression
(Expr
) then
7211 Flag_Non_Static_Expr
7212 ("Scalar_Storage_Order requires static expression!", Expr
);
7214 elsif (Expr_Value
(Expr
) = 0) /= Bytes_Big_Endian
then
7216 -- Here for the case of a non-default (i.e. non-confirming)
7217 -- Scalar_Storage_Order attribute definition.
7219 if Support_Nondefault_SSO_On_Target
then
7220 Set_Reverse_Storage_Order
(Base_Type
(U_Ent
), True);
7223 ("non-default Scalar_Storage_Order not supported on "
7228 -- Clear SSO default indications since explicit setting of the
7229 -- order overrides the defaults.
7231 Set_SSO_Set_Low_By_Default
(Base_Type
(U_Ent
), False);
7232 Set_SSO_Set_High_By_Default
(Base_Type
(U_Ent
), False);
7235 ------------------------
7236 -- Size or Value_Size --
7237 ------------------------
7239 -- Size or Value_Size attribute definition clause. These are treated
7240 -- the same, except that Size is allowed on objects, and Value_Size
7241 -- is allowed on nonfirst subtypes. First subtypes allow both Size
7242 -- and Value_Size; the treatment is the same for both.
7244 when Attribute_Size | Attribute_Value_Size
=> Size
: declare
7245 Size
: constant Uint
:= Static_Integer
(Expr
);
7247 Attr_Name
: constant String :=
7248 (if Id
= Attribute_Size
then "size"
7249 elsif Id
= Attribute_Value_Size
then "value size"
7250 else ""); -- can't happen
7251 -- Name of the attribute for printing in messages
7253 OK_Prefix
: constant Boolean :=
7254 (if Id
= Attribute_Size
then
7255 Ekind
(U_Ent
) in Type_Kind | Constant_Or_Variable_Kind
7256 elsif Id
= Attribute_Value_Size
then
7257 Ekind
(U_Ent
) in Type_Kind
7258 else False); -- can't happen
7259 -- For X'Size, X can be a type or object; for X'Value_Size,
7260 -- X can be a type. Note that we already checked that 'Size
7261 -- can be specified only for a first subtype.
7266 if not OK_Prefix
then
7267 Error_Msg_N
(Attr_Name
& " cannot be given for &", Nam
);
7269 elsif Duplicate_Clause
then
7272 elsif Is_Array_Type
(U_Ent
)
7273 and then not Is_Constrained
(U_Ent
)
7276 (Attr_Name
& " cannot be given for unconstrained array", Nam
);
7278 elsif Present
(Size
) then
7280 Etyp
: constant Entity_Id
:=
7281 (if Is_Type
(U_Ent
) then U_Ent
else Etype
(U_Ent
));
7284 -- Check size, note that Gigi is in charge of checking that
7285 -- the size of an array or record type is OK. Also we do not
7286 -- check the size in the ordinary fixed-point case, since
7287 -- it is too early to do so (there may be subsequent small
7288 -- clause that affects the size). We can check the size if
7289 -- a small clause has already been given.
7291 if not Is_Ordinary_Fixed_Point_Type
(U_Ent
)
7292 or else Has_Small_Clause
(U_Ent
)
7297 Check_Size
(Expr
, Etyp
, Size
, Biased
);
7298 Set_Biased
(U_Ent
, N
, Attr_Name
& " clause", Biased
);
7302 -- For types, set RM_Size and Esize if appropriate
7304 if Is_Type
(U_Ent
) then
7305 Set_RM_Size
(U_Ent
, Size
);
7307 -- If we are specifying the Size or Value_Size of a
7308 -- first subtype, then for elementary types, increase
7309 -- Object_Size to power of 2, but not less than a storage
7310 -- unit in any case (normally this means it will be byte
7313 -- For all other types, nothing else to do, we leave
7314 -- Esize (object size) unset; the back end will set it
7315 -- from the size and alignment in an appropriate manner.
7317 -- In both cases, we check whether the alignment must be
7318 -- reset in the wake of the size change.
7320 -- For nonfirst subtypes ('Value_Size only), we do
7323 if Is_First_Subtype
(U_Ent
) then
7324 if Is_Elementary_Type
(U_Ent
) then
7325 if Size
<= System_Storage_Unit
then
7327 (U_Ent
, UI_From_Int
(System_Storage_Unit
));
7328 elsif Size
<= 16 then
7329 Set_Esize
(U_Ent
, Uint_16
);
7330 elsif Size
<= 32 then
7331 Set_Esize
(U_Ent
, Uint_32
);
7333 Set_Esize
(U_Ent
, (Size
+ 63) / 64 * 64);
7336 Alignment_Check_For_Size_Change
7337 (U_Ent
, Esize
(U_Ent
));
7339 Alignment_Check_For_Size_Change
(U_Ent
, Size
);
7343 -- For Object'Size, set Esize only
7346 if Is_Elementary_Type
(Etyp
)
7347 and then Size
/= System_Storage_Unit
7351 and then Size
/= System_Max_Integer_Size
7353 Error_Msg_Uint_1
:= UI_From_Int
(System_Storage_Unit
);
7355 UI_From_Int
(System_Max_Integer_Size
);
7357 ("size for primitive object must be a power of 2 in "
7358 & "the range ^-^", N
);
7361 Set_Esize
(U_Ent
, Size
);
7364 -- As of RM 13.1, only confirming size
7365 -- (i.e. (Size = Esize (Etyp))) for aliased object of
7366 -- elementary type must be supported.
7367 -- GNAT rejects nonconfirming size for such object.
7369 if Is_Aliased
(U_Ent
)
7370 and then Is_Elementary_Type
(Etyp
)
7371 and then Known_Esize
(U_Ent
)
7372 and then Size
/= Esize
(Etyp
)
7375 ("nonconfirming Size for aliased object is not "
7379 Set_Has_Size_Clause
(U_Ent
);
7388 -- Small attribute definition clause
7390 when Attribute_Small
=> Small
: declare
7391 Implicit_Base
: constant Entity_Id
:= Base_Type
(U_Ent
);
7395 Analyze_And_Resolve
(Expr
, Any_Real
);
7397 if Etype
(Expr
) = Any_Type
then
7400 elsif not Is_OK_Static_Expression
(Expr
) then
7401 Flag_Non_Static_Expr
7402 ("small requires static expression!", Expr
);
7406 Small
:= Expr_Value_R
(Expr
);
7408 if Small
<= Ureal_0
then
7409 Error_Msg_N
("small value must be greater than zero", Expr
);
7415 if not Is_Ordinary_Fixed_Point_Type
(U_Ent
) then
7417 ("small requires an ordinary fixed point type", Nam
);
7419 elsif Has_Small_Clause
(U_Ent
) then
7420 Error_Msg_N
("small already given for &", Nam
);
7422 elsif Small
> Delta_Value
(U_Ent
) then
7424 ("small value must not be greater than delta value", Nam
);
7427 Set_Small_Value
(U_Ent
, Small
);
7428 Set_Small_Value
(Implicit_Base
, Small
);
7429 Set_Has_Small_Clause
(U_Ent
);
7430 Set_Has_Small_Clause
(Implicit_Base
);
7431 Set_Has_Non_Standard_Rep
(Implicit_Base
);
7439 -- Storage_Pool attribute definition clause
7441 when Attribute_Simple_Storage_Pool
7442 | Attribute_Storage_Pool
7444 Storage_Pool
: declare
7448 procedure Associate_Storage_Pool
7449 (Ent
: Entity_Id
; Pool
: Entity_Id
);
7450 -- Associate Pool to Ent and perform legality checks on subpools
7452 ----------------------------
7453 -- Associate_Storage_Pool --
7454 ----------------------------
7456 procedure Associate_Storage_Pool
7457 (Ent
: Entity_Id
; Pool
: Entity_Id
)
7459 function Object_From
(Pool
: Entity_Id
) return Entity_Id
;
7460 -- Return the entity of which Pool is a part of
7466 function Object_From
7467 (Pool
: Entity_Id
) return Entity_Id
7469 N
: Node_Id
:= Pool
;
7471 if Present
(Renamed_Object
(Pool
)) then
7472 N
:= Renamed_Object
(Pool
);
7475 while Present
(N
) loop
7477 when N_Defining_Identifier
=>
7480 when N_Identifier | N_Expanded_Name
=>
7483 when N_Indexed_Component | N_Selected_Component |
7484 N_Explicit_Dereference
7488 when N_Type_Conversion
=>
7489 N
:= Expression
(N
);
7492 -- ??? we probably should handle more cases but
7493 -- this is good enough in practice for this check
7494 -- on a corner case.
7506 Set_Associated_Storage_Pool
(Ent
, Pool
);
7508 -- Check RM 13.11.4(22-23/3): a specification of a storage pool
7509 -- is illegal if the storage pool supports subpools and:
7510 -- (A) The access type is a general access type.
7511 -- (B) The access type is statically deeper than the storage
7513 -- (C) The storage pool object is a part of a formal parameter;
7514 -- (D) The storage pool object is a part of the dereference of
7515 -- a non-library level general access type;
7517 if Ada_Version
>= Ada_2012
7518 and then RTU_Loaded
(System_Storage_Pools_Subpools
)
7520 Is_Ancestor
(RTE
(RE_Root_Storage_Pool_With_Subpools
),
7525 if Ekind
(Etype
(Ent
)) = E_General_Access_Type
then
7527 ("subpool cannot be used on general access type", Ent
);
7532 if Type_Access_Level
(Ent
)
7533 > Static_Accessibility_Level
7534 (Pool
, Object_Decl_Level
)
7537 ("subpool access type has deeper accessibility "
7538 & "level than pool", Ent
);
7542 Obj
:= Object_From
(Pool
);
7546 if Present
(Obj
) and then Is_Formal
(Obj
) then
7548 ("subpool cannot be part of a parameter", Ent
);
7555 and then Ekind
(Etype
(Obj
)) = E_General_Access_Type
7556 and then not Is_Library_Level_Entity
(Etype
(Obj
))
7559 ("subpool cannot be part of the dereference of a " &
7560 "nested general access type", Ent
);
7564 end Associate_Storage_Pool
;
7567 if Ekind
(U_Ent
) = E_Access_Subprogram_Type
then
7569 ("storage pool cannot be given for access-to-subprogram type",
7573 elsif Ekind
(U_Ent
) not in E_Access_Type | E_General_Access_Type
7576 ("storage pool can only be given for access types", Nam
);
7579 elsif Is_Derived_Type
(U_Ent
) then
7581 ("storage pool cannot be given for a derived access type",
7584 elsif Duplicate_Clause
then
7587 elsif Present
(Associated_Storage_Pool
(U_Ent
)) then
7588 Error_Msg_N
("storage pool already given for &", Nam
);
7592 -- Check for Storage_Size previously given
7595 SS
: constant Node_Id
:=
7596 Get_Attribute_Definition_Clause
7597 (U_Ent
, Attribute_Storage_Size
);
7599 if Present
(SS
) then
7600 Check_Pool_Size_Clash
(U_Ent
, N
, SS
);
7604 -- Storage_Pool case
7606 if Id
= Attribute_Storage_Pool
then
7608 (Expr
, Class_Wide_Type
(RTE
(RE_Root_Storage_Pool
)));
7610 -- In the Simple_Storage_Pool case, we allow a variable of any
7611 -- simple storage pool type, so we Resolve without imposing an
7615 Analyze_And_Resolve
(Expr
);
7617 if No
(Get_Rep_Pragma
7618 (Etype
(Expr
), Name_Simple_Storage_Pool_Type
))
7621 ("expression must be of a simple storage pool type", Expr
);
7625 if not Denotes_Variable
(Expr
) then
7626 Error_Msg_N
("storage pool must be a variable", Expr
);
7630 if Nkind
(Expr
) = N_Type_Conversion
then
7631 T
:= Etype
(Expression
(Expr
));
7636 -- The Stack_Bounded_Pool is used internally for implementing
7637 -- access types with a Storage_Size. Since it only work properly
7638 -- when used on one specific type, we need to check that it is not
7639 -- hijacked improperly:
7641 -- type T is access Integer;
7642 -- for T'Storage_Size use n;
7643 -- type Q is access Float;
7644 -- for Q'Storage_Size use T'Storage_Size; -- incorrect
7646 if Is_RTE
(Base_Type
(T
), RE_Stack_Bounded_Pool
) then
7647 Error_Msg_N
("non-shareable internal Pool", Expr
);
7651 -- Validate_Remote_Access_To_Class_Wide_Type for attribute
7652 -- Storage_Pool since this attribute cannot be defined for such
7653 -- types (RM E.2.2(17)).
7655 Validate_Remote_Access_To_Class_Wide_Type
(N
);
7657 -- If the argument is a name that is not an entity name, then
7658 -- we construct a renaming operation to define an entity of
7659 -- type storage pool.
7661 if not Is_Entity_Name
(Expr
)
7662 and then Is_Object_Reference
(Expr
)
7664 Pool
:= Make_Temporary
(Loc
, 'P', Expr
);
7667 Rnode
: constant Node_Id
:=
7668 Make_Object_Renaming_Declaration
(Loc
,
7669 Defining_Identifier
=> Pool
,
7671 New_Occurrence_Of
(Etype
(Expr
), Loc
),
7675 -- If the attribute definition clause comes from an aspect
7676 -- clause, then insert the renaming before the associated
7677 -- entity's declaration, since the attribute clause has
7678 -- not yet been appended to the declaration list.
7680 if From_Aspect_Specification
(N
) then
7681 Insert_Before
(Parent
(Entity
(N
)), Rnode
);
7683 Insert_Before
(N
, Rnode
);
7687 Associate_Storage_Pool
(U_Ent
, Pool
);
7690 elsif Is_Entity_Name
(Expr
) then
7691 Pool
:= Entity
(Expr
);
7693 -- If pool is a renamed object, get original one. This can
7694 -- happen with an explicit renaming, and within instances.
7696 while Present
(Renamed_Object
(Pool
))
7697 and then Is_Entity_Name
(Renamed_Object
(Pool
))
7699 Pool
:= Entity
(Renamed_Object
(Pool
));
7702 if Present
(Renamed_Object
(Pool
))
7703 and then Nkind
(Renamed_Object
(Pool
)) = N_Type_Conversion
7704 and then Is_Entity_Name
(Expression
(Renamed_Object
(Pool
)))
7706 Pool
:= Entity
(Expression
(Renamed_Object
(Pool
)));
7709 Associate_Storage_Pool
(U_Ent
, Pool
);
7711 elsif Nkind
(Expr
) = N_Type_Conversion
7712 and then Is_Entity_Name
(Expression
(Expr
))
7713 and then Nkind
(Original_Node
(Expr
)) = N_Attribute_Reference
7715 Pool
:= Entity
(Expression
(Expr
));
7716 Associate_Storage_Pool
(U_Ent
, Pool
);
7719 Error_Msg_N
("incorrect reference to a Storage Pool", Expr
);
7728 -- Storage_Size attribute definition clause
7730 when Attribute_Storage_Size
=> Storage_Size
: declare
7731 Btype
: constant Entity_Id
:= Base_Type
(U_Ent
);
7734 if Is_Task_Type
(U_Ent
) then
7736 -- Check obsolescent (but never obsolescent if from aspect)
7738 if not From_Aspect_Specification
(N
) then
7739 Check_Restriction
(No_Obsolescent_Features
, N
);
7741 if Warn_On_Obsolescent_Feature
then
7743 ("?j?storage size clause for task is an obsolescent "
7744 & "feature (RM J.9)", N
);
7745 Error_Msg_N
("\?j?use Storage_Size pragma instead", N
);
7752 if not Is_Access_Type
(U_Ent
)
7753 and then Ekind
(U_Ent
) /= E_Task_Type
7755 Error_Msg_N
("storage size cannot be given for &", Nam
);
7757 elsif Is_Access_Type
(U_Ent
) and Is_Derived_Type
(U_Ent
) then
7759 ("storage size cannot be given for a derived access type",
7762 elsif Duplicate_Clause
then
7766 -- Validate_Remote_Access_To_Class_Wide_Type for attribute
7767 -- Storage_Size since this attribute cannot be defined for such
7768 -- types (RM E.2.2(17)).
7770 Validate_Remote_Access_To_Class_Wide_Type
(N
);
7772 Analyze_And_Resolve
(Expr
, Any_Integer
);
7774 if Is_Access_Type
(U_Ent
) then
7776 -- Check for Storage_Pool previously given
7779 SP
: constant Node_Id
:=
7780 Get_Attribute_Definition_Clause
7781 (U_Ent
, Attribute_Storage_Pool
);
7784 if Present
(SP
) then
7785 Check_Pool_Size_Clash
(U_Ent
, SP
, N
);
7789 -- Special case of for x'Storage_Size use 0
7791 if Is_OK_Static_Expression
(Expr
)
7792 and then Expr_Value
(Expr
) = 0
7794 Set_No_Pool_Assigned
(Btype
);
7798 Set_Has_Storage_Size_Clause
(Btype
);
7806 when Attribute_Stream_Size
=> Stream_Size
: declare
7807 Size
: constant Uint
:= Static_Integer
(Expr
);
7810 if Ada_Version
<= Ada_95
then
7811 Check_Restriction
(No_Implementation_Attributes
, N
);
7814 if Duplicate_Clause
then
7817 elsif Is_Elementary_Type
(U_Ent
) then
7818 -- Size will be empty if we already detected an error
7819 -- (e.g. Expr is of the wrong type); we might as well
7820 -- give the useful hint below even in that case.
7822 if No
(Size
) or else
7823 (Size
/= System_Storage_Unit
7824 and then Size
/= System_Storage_Unit
* 2
7825 and then Size
/= System_Storage_Unit
* 3
7826 and then Size
/= System_Storage_Unit
* 4
7827 and then Size
/= System_Storage_Unit
* 8)
7830 ("stream size for elementary type must be 8, 16, 24, " &
7833 elsif Known_RM_Size
(U_Ent
) and then RM_Size
(U_Ent
) > Size
then
7834 Error_Msg_Uint_1
:= RM_Size
(U_Ent
);
7836 ("stream size for elementary type must be 8, 16, 24, " &
7837 "32 or 64 and at least ^", N
);
7840 Set_Has_Stream_Size_Clause
(U_Ent
);
7843 Error_Msg_N
("Stream_Size cannot be given for &", Nam
);
7847 -----------------------
7848 -- Variable_Indexing --
7849 -----------------------
7851 when Attribute_Variable_Indexing
=>
7852 Check_Indexing_Functions
;
7858 when Attribute_Write
=>
7859 Analyze_Stream_TSS_Definition
(TSS_Stream_Write
);
7860 Set_Has_Specified_Stream_Write
(Ent
);
7862 -- All other attributes cannot be set
7866 ("attribute& cannot be set with definition clause", N
);
7869 -- The test for the type being frozen must be performed after any
7870 -- expression the clause has been analyzed since the expression itself
7871 -- might cause freezing that makes the clause illegal.
7873 if Rep_Item_Too_Late
(U_Ent
, N
, FOnly
) then
7876 end Analyze_Attribute_Definition_Clause
;
7878 ----------------------------
7879 -- Analyze_Code_Statement --
7880 ----------------------------
7882 procedure Analyze_Code_Statement
(N
: Node_Id
) is
7883 HSS
: constant Node_Id
:= Parent
(N
);
7884 SBody
: constant Node_Id
:= Parent
(HSS
);
7885 Subp
: constant Entity_Id
:= Current_Scope
;
7892 -- Accept foreign code statements for CodePeer. The analysis is skipped
7893 -- to avoid rejecting unrecognized constructs.
7895 if CodePeer_Mode
then
7900 -- Analyze and check we get right type, note that this implements the
7901 -- requirement (RM 13.8(1)) that Machine_Code be with'ed, since that is
7902 -- the only way that Asm_Insn could possibly be visible.
7904 Analyze_And_Resolve
(Expression
(N
));
7906 if Etype
(Expression
(N
)) = Any_Type
then
7908 elsif not Is_RTE
(Etype
(Expression
(N
)), RE_Asm_Insn
) then
7909 Error_Msg_N
("incorrect type for code statement", N
);
7913 Check_Code_Statement
(N
);
7915 -- Make sure we appear in the handled statement sequence of a subprogram
7918 if Nkind
(HSS
) /= N_Handled_Sequence_Of_Statements
7919 or else Nkind
(SBody
) /= N_Subprogram_Body
7922 ("code statement can only appear in body of subprogram", N
);
7926 -- Do remaining checks (RM 13.8(3)) if not already done
7928 if not Is_Machine_Code_Subprogram
(Subp
) then
7929 Set_Is_Machine_Code_Subprogram
(Subp
);
7931 -- No exception handlers allowed
7933 if Present
(Exception_Handlers
(HSS
)) then
7935 ("exception handlers not permitted in machine code subprogram",
7936 First
(Exception_Handlers
(HSS
)));
7939 -- No declarations other than use clauses and pragmas (we allow
7940 -- certain internally generated declarations as well).
7942 Decl
:= First
(Declarations
(SBody
));
7943 while Present
(Decl
) loop
7944 DeclO
:= Original_Node
(Decl
);
7945 if Comes_From_Source
(DeclO
)
7946 and Nkind
(DeclO
) not in N_Pragma
7947 | N_Use_Package_Clause
7949 | N_Implicit_Label_Declaration
7952 ("this declaration is not allowed in machine code subprogram",
7959 -- No statements other than code statements, pragmas, and labels.
7960 -- Again we allow certain internally generated statements.
7962 -- In Ada 2012, qualified expressions are names, and the code
7963 -- statement is initially parsed as a procedure call.
7965 Stmt
:= First
(Statements
(HSS
));
7966 while Present
(Stmt
) loop
7967 StmtO
:= Original_Node
(Stmt
);
7969 -- A procedure call transformed into a code statement is OK
7971 if Ada_Version
>= Ada_2012
7972 and then Nkind
(StmtO
) = N_Procedure_Call_Statement
7973 and then Nkind
(Name
(StmtO
)) = N_Qualified_Expression
7977 elsif Comes_From_Source
(StmtO
)
7978 and then Nkind
(StmtO
) not in
7979 N_Pragma | N_Label | N_Code_Statement
7982 ("this statement is not allowed in machine code subprogram",
7989 end Analyze_Code_Statement
;
7991 -----------------------------------------------
7992 -- Analyze_Enumeration_Representation_Clause --
7993 -----------------------------------------------
7995 procedure Analyze_Enumeration_Representation_Clause
(N
: Node_Id
) is
7996 Ident
: constant Node_Id
:= Identifier
(N
);
7997 Aggr
: constant Node_Id
:= Array_Aggregate
(N
);
7998 Enumtype
: Entity_Id
;
8005 Err
: Boolean := False;
8006 -- Set True to avoid cascade errors and crashes on incorrect source code
8008 Lo
: constant Uint
:= Expr_Value
(Type_Low_Bound
(Universal_Integer
));
8009 Hi
: constant Uint
:= Expr_Value
(Type_High_Bound
(Universal_Integer
));
8010 -- Allowed range of universal integer (= allowed range of enum lit vals)
8014 -- Minimum and maximum values of entries
8016 Max_Node
: Node_Id
:= Empty
; -- init to avoid warning
8017 -- Pointer to node for literal providing max value
8020 if Ignore_Rep_Clauses
then
8021 Kill_Rep_Clause
(N
);
8025 -- Ignore enumeration rep clauses by default in CodePeer mode,
8026 -- unless -gnatd.I is specified, as a work around for potential false
8027 -- positive messages.
8029 if CodePeer_Mode
and not Debug_Flag_Dot_II
then
8033 -- First some basic error checks
8036 Enumtype
:= Entity
(Ident
);
8038 if Enumtype
= Any_Type
8039 or else Rep_Item_Too_Early
(Enumtype
, N
)
8043 Enumtype
:= Underlying_Type
(Enumtype
);
8046 if not Is_Enumeration_Type
(Enumtype
) then
8048 ("enumeration type required, found}",
8049 Ident
, First_Subtype
(Enumtype
));
8053 -- Ignore rep clause on generic actual type. This will already have
8054 -- been flagged on the template as an error, and this is the safest
8055 -- way to ensure we don't get a junk cascaded message in the instance.
8057 if Is_Generic_Actual_Type
(Enumtype
) then
8060 -- Type must be in current scope
8062 elsif Scope
(Enumtype
) /= Current_Scope
then
8063 Error_Msg_N
("type must be declared in this scope", Ident
);
8066 -- Type must be a first subtype
8068 elsif not Is_First_Subtype
(Enumtype
) then
8069 Error_Msg_N
("cannot give enumeration rep clause for subtype", N
);
8072 -- Ignore duplicate rep clause
8074 elsif Has_Enumeration_Rep_Clause
(Enumtype
) then
8075 Error_Msg_N
("duplicate enumeration rep clause ignored", N
);
8078 -- Don't allow rep clause for standard [wide_[wide_]]character
8080 elsif Is_Standard_Character_Type
(Enumtype
) then
8081 Error_Msg_N
("enumeration rep clause not allowed for this type", N
);
8084 -- Check that the expression is a proper aggregate (no parentheses)
8086 elsif Paren_Count
(Aggr
) /= 0 then
8088 ("extra parentheses surrounding aggregate not allowed", Aggr
);
8091 -- Reject the mixing of named and positional entries in the aggregate
8093 elsif Present
(Expressions
(Aggr
))
8094 and then Present
(Component_Associations
(Aggr
))
8096 Error_Msg_N
("cannot mix positional and named entries in "
8097 & "enumeration rep clause", N
);
8100 -- All tests passed, so set rep clause in place
8103 Set_Has_Enumeration_Rep_Clause
(Enumtype
);
8104 Set_Has_Enumeration_Rep_Clause
(Base_Type
(Enumtype
));
8107 -- Now we process the aggregate. Note that we don't use the normal
8108 -- aggregate code for this purpose, because we don't want any of the
8109 -- normal expansion activities, and a number of special semantic
8110 -- rules apply (including the component type being any integer type)
8112 Elit
:= First_Literal
(Enumtype
);
8114 -- Process positional entries
8116 if Present
(Expressions
(Aggr
)) then
8117 Expr
:= First
(Expressions
(Aggr
));
8118 while Present
(Expr
) loop
8120 Error_Msg_N
("too many entries in aggregate", Expr
);
8124 Val
:= Static_Integer
(Expr
);
8126 -- Err signals that we found some incorrect entries processing
8127 -- the list. The final checks for completeness and ordering are
8128 -- skipped in this case.
8133 elsif Val
< Lo
or else Hi
< Val
then
8134 Error_Msg_N
("value outside permitted range", Expr
);
8138 Set_Enumeration_Rep
(Elit
, Val
);
8139 Set_Enumeration_Rep_Expr
(Elit
, Expr
);
8146 -- Process named entries
8148 elsif Present
(Component_Associations
(Aggr
)) then
8149 Assoc
:= First
(Component_Associations
(Aggr
));
8150 while Present
(Assoc
) loop
8151 Choice
:= First
(Choices
(Assoc
));
8153 if Present
(Next
(Choice
)) then
8155 ("multiple choice not allowed here", Next
(Choice
));
8159 if Nkind
(Choice
) = N_Others_Choice
then
8160 Error_Msg_N
("OTHERS choice not allowed here", Choice
);
8163 elsif Nkind
(Choice
) = N_Range
then
8165 -- ??? should allow zero/one element range here
8167 Error_Msg_N
("range not allowed here", Choice
);
8171 Analyze_And_Resolve
(Choice
, Enumtype
);
8173 if Error_Posted
(Choice
) then
8178 if Is_Entity_Name
(Choice
)
8179 and then Is_Type
(Entity
(Choice
))
8181 Error_Msg_N
("subtype name not allowed here", Choice
);
8184 -- ??? should allow static subtype with zero/one entry
8186 elsif Etype
(Choice
) = Base_Type
(Enumtype
) then
8187 if not Is_OK_Static_Expression
(Choice
) then
8188 Flag_Non_Static_Expr
8189 ("non-static expression used for choice!", Choice
);
8193 Elit
:= Expr_Value_E
(Choice
);
8195 if Present
(Enumeration_Rep_Expr
(Elit
)) then
8197 Sloc
(Enumeration_Rep_Expr
(Elit
));
8199 ("representation for& previously given#",
8204 Set_Enumeration_Rep_Expr
(Elit
, Expression
(Assoc
));
8206 Expr
:= Expression
(Assoc
);
8207 Val
:= Static_Integer
(Expr
);
8212 elsif Val
< Lo
or else Hi
< Val
then
8213 Error_Msg_N
("value outside permitted range", Expr
);
8217 Set_Enumeration_Rep
(Elit
, Val
);
8228 -- Aggregate is fully processed. Now we check that a full set of
8229 -- representations was given, and that they are in range and in order.
8230 -- These checks are only done if no other errors occurred.
8236 Elit
:= First_Literal
(Enumtype
);
8237 while Present
(Elit
) loop
8238 if No
(Enumeration_Rep_Expr
(Elit
)) then
8239 Error_Msg_NE
("missing representation for&!", N
, Elit
);
8242 Val
:= Enumeration_Rep
(Elit
);
8248 if Present
(Val
) then
8249 if Present
(Max
) and then Val
<= Max
then
8251 ("enumeration value for& not ordered!",
8252 Enumeration_Rep_Expr
(Elit
), Elit
);
8255 Max_Node
:= Enumeration_Rep_Expr
(Elit
);
8259 -- If there is at least one literal whose representation is not
8260 -- equal to the Pos value, then note that this enumeration type
8261 -- has a non-standard representation.
8263 if Val
/= Enumeration_Pos
(Elit
) then
8264 Set_Has_Non_Standard_Rep
(Base_Type
(Enumtype
));
8271 -- Now set proper size information
8274 Minsize
: Uint
:= UI_From_Int
(Minimum_Size
(Enumtype
));
8277 if Has_Size_Clause
(Enumtype
) then
8279 -- All OK, if size is OK now
8281 if RM_Size
(Enumtype
) >= Minsize
then
8285 -- Try if we can get by with biasing
8288 UI_From_Int
(Minimum_Size
(Enumtype
, Biased
=> True));
8290 -- Error message if even biasing does not work
8292 if RM_Size
(Enumtype
) < Minsize
then
8293 Error_Msg_Uint_1
:= RM_Size
(Enumtype
);
8294 Error_Msg_Uint_2
:= Max
;
8296 ("previously given size (^) is too small "
8297 & "for this value (^)", Max_Node
);
8299 -- If biasing worked, indicate that we now have biased rep
8303 (Enumtype
, Size_Clause
(Enumtype
), "size clause");
8308 Set_RM_Size
(Enumtype
, Minsize
);
8309 Set_Enum_Esize
(Enumtype
);
8312 Set_RM_Size
(Base_Type
(Enumtype
), RM_Size
(Enumtype
));
8313 Set_Esize
(Base_Type
(Enumtype
), Esize
(Enumtype
));
8315 Copy_Alignment
(To
=> Base_Type
(Enumtype
), From
=> Enumtype
);
8319 -- We repeat the too late test in case it froze itself
8321 if Rep_Item_Too_Late
(Enumtype
, N
) then
8324 end Analyze_Enumeration_Representation_Clause
;
8326 ----------------------------
8327 -- Analyze_Free_Statement --
8328 ----------------------------
8330 procedure Analyze_Free_Statement
(N
: Node_Id
) is
8332 Analyze
(Expression
(N
));
8333 end Analyze_Free_Statement
;
8335 ---------------------------
8336 -- Analyze_Freeze_Entity --
8337 ---------------------------
8339 procedure Analyze_Freeze_Entity
(N
: Node_Id
) is
8341 Freeze_Entity_Checks
(N
);
8342 end Analyze_Freeze_Entity
;
8344 -----------------------------------
8345 -- Analyze_Freeze_Generic_Entity --
8346 -----------------------------------
8348 procedure Analyze_Freeze_Generic_Entity
(N
: Node_Id
) is
8349 E
: constant Entity_Id
:= Entity
(N
);
8352 if not Is_Frozen
(E
) and then Has_Delayed_Aspects
(E
) then
8353 Analyze_Aspects_At_Freeze_Point
(E
);
8356 Freeze_Entity_Checks
(N
);
8357 end Analyze_Freeze_Generic_Entity
;
8359 ------------------------------------------
8360 -- Analyze_Record_Representation_Clause --
8361 ------------------------------------------
8363 -- Note: we check as much as we can here, but we can't do any checks
8364 -- based on the position values (e.g. overlap checks) until freeze time
8365 -- because especially in Ada 2005 (machine scalar mode), the processing
8366 -- for non-standard bit order can substantially change the positions.
8367 -- See procedure Check_Record_Representation_Clause (called from Freeze)
8368 -- for the remainder of this processing.
8370 procedure Analyze_Record_Representation_Clause
(N
: Node_Id
) is
8371 Ident
: constant Node_Id
:= Identifier
(N
);
8379 Rectype
: Entity_Id
;
8382 function Is_Inherited
(Comp
: Entity_Id
) return Boolean;
8383 -- True if Comp is an inherited component in a record extension
8389 function Is_Inherited
(Comp
: Entity_Id
) return Boolean is
8390 Comp_Base
: Entity_Id
;
8393 if Ekind
(Rectype
) = E_Record_Subtype
then
8394 Comp_Base
:= Original_Record_Component
(Comp
);
8399 return Comp_Base
/= Original_Record_Component
(Comp_Base
);
8404 Is_Record_Extension
: Boolean;
8405 -- True if Rectype is a record extension
8407 CR_Pragma
: Node_Id
:= Empty
;
8408 -- Points to N_Pragma node if Complete_Representation pragma present
8410 -- Start of processing for Analyze_Record_Representation_Clause
8413 if Ignore_Rep_Clauses
then
8414 Kill_Rep_Clause
(N
);
8419 Rectype
:= Entity
(Ident
);
8421 if Rectype
= Any_Type
or else Rep_Item_Too_Early
(Rectype
, N
) then
8424 Rectype
:= Underlying_Type
(Rectype
);
8427 -- First some basic error checks
8429 if not Is_Record_Type
(Rectype
) then
8431 ("record type required, found}", Ident
, First_Subtype
(Rectype
));
8434 elsif Scope
(Rectype
) /= Current_Scope
then
8435 Error_Msg_N
("type must be declared in this scope", N
);
8438 elsif not Is_First_Subtype
(Rectype
) then
8439 Error_Msg_N
("cannot give record rep clause for subtype", N
);
8442 elsif Has_Record_Rep_Clause
(Rectype
) then
8443 Error_Msg_N
("duplicate record rep clause ignored", N
);
8446 elsif Rep_Item_Too_Late
(Rectype
, N
) then
8450 -- We know we have a first subtype, now possibly go to the anonymous
8451 -- base type to determine whether Rectype is a record extension.
8453 Recdef
:= Type_Definition
(Declaration_Node
(Base_Type
(Rectype
)));
8454 Is_Record_Extension
:=
8455 Nkind
(Recdef
) = N_Derived_Type_Definition
8456 and then Present
(Record_Extension_Part
(Recdef
));
8458 if Present
(Mod_Clause
(N
)) then
8460 M
: constant Node_Id
:= Mod_Clause
(N
);
8461 P
: constant List_Id
:= Pragmas_Before
(M
);
8465 Check_Restriction
(No_Obsolescent_Features
, Mod_Clause
(N
));
8467 if Warn_On_Obsolescent_Feature
then
8469 ("?j?mod clause is an obsolescent feature (RM J.8)", N
);
8471 ("\?j?use alignment attribute definition clause instead", N
);
8478 -- Get the alignment value to perform error checking
8480 Ignore
:= Get_Alignment_Value
(Expression
(M
));
8484 -- For untagged types, clear any existing component clauses for the
8485 -- type. If the type is derived, this is what allows us to override
8486 -- a rep clause for the parent. For type extensions, the representation
8487 -- of the inherited components is inherited, so we want to keep previous
8488 -- component clauses for completeness.
8490 if not Is_Tagged_Type
(Rectype
) then
8491 Comp
:= First_Component_Or_Discriminant
(Rectype
);
8492 while Present
(Comp
) loop
8493 Set_Component_Clause
(Comp
, Empty
);
8494 Next_Component_Or_Discriminant
(Comp
);
8498 -- All done if no component clauses
8500 CC
:= First
(Component_Clauses
(N
));
8506 -- A representation like this applies to the base type
8508 Set_Has_Record_Rep_Clause
(Base_Type
(Rectype
));
8509 Set_Has_Non_Standard_Rep
(Base_Type
(Rectype
));
8510 Set_Has_Specified_Layout
(Base_Type
(Rectype
));
8512 -- Process the component clauses
8514 while Present
(CC
) loop
8518 if Nkind
(CC
) = N_Pragma
then
8521 -- The only pragma of interest is Complete_Representation
8523 if Pragma_Name
(CC
) = Name_Complete_Representation
then
8527 -- Processing for real component clause
8530 Posit
:= Static_Integer
(Position
(CC
));
8531 Fbit
:= Static_Integer
(First_Bit
(CC
));
8532 Lbit
:= Static_Integer
(Last_Bit
(CC
));
8535 and then Present
(Fbit
)
8536 and then Present
(Lbit
)
8539 Error_Msg_N
("position cannot be negative", Position
(CC
));
8542 Error_Msg_N
("first bit cannot be negative", First_Bit
(CC
));
8544 -- The Last_Bit specified in a component clause must not be
8545 -- less than the First_Bit minus one (RM-13.5.1(10)).
8547 elsif Lbit
< Fbit
- 1 then
8549 ("last bit cannot be less than first bit minus one",
8552 -- Values look OK, so find the corresponding record component
8553 -- Even though the syntax allows an attribute reference for
8554 -- implementation-defined components, GNAT does not allow the
8555 -- tag to get an explicit position.
8557 elsif Nkind
(Component_Name
(CC
)) = N_Attribute_Reference
then
8558 if Attribute_Name
(Component_Name
(CC
)) = Name_Tag
then
8559 Error_Msg_N
("position of tag cannot be specified", CC
);
8561 Error_Msg_N
("illegal component name", CC
);
8565 Comp
:= First_Entity
(Rectype
);
8566 while Present
(Comp
) loop
8567 exit when Chars
(Comp
) = Chars
(Component_Name
(CC
));
8573 -- Maybe component of base type that is absent from
8574 -- statically constrained first subtype.
8576 Comp
:= First_Entity
(Base_Type
(Rectype
));
8577 while Present
(Comp
) loop
8578 exit when Chars
(Comp
) = Chars
(Component_Name
(CC
));
8585 ("component clause is for non-existent field", CC
);
8587 -- Ada 2012 (AI05-0026): Any name that denotes a
8588 -- discriminant of an object of an unchecked union type
8589 -- shall not occur within a record_representation_clause.
8591 -- The general restriction of using record rep clauses on
8592 -- Unchecked_Union types has now been lifted. Since it is
8593 -- possible to introduce a record rep clause which mentions
8594 -- the discriminant of an Unchecked_Union in non-Ada 2012
8595 -- code, this check is applied to all versions of the
8598 elsif Ekind
(Comp
) = E_Discriminant
8599 and then Is_Unchecked_Union
(Rectype
)
8602 ("cannot reference discriminant of unchecked union",
8603 Component_Name
(CC
));
8605 elsif Is_Record_Extension
and then Is_Inherited
(Comp
) then
8607 ("component clause not allowed for inherited "
8608 & "component&", CC
, Comp
);
8610 elsif Present
(Component_Clause
(Comp
)) then
8612 -- Diagnose duplicate rep clause, or check consistency
8613 -- if this is an inherited component. In a double fault,
8614 -- there may be a duplicate inconsistent clause for an
8615 -- inherited component.
8617 if Scope
(Original_Record_Component
(Comp
)) = Rectype
8618 or else Parent
(Component_Clause
(Comp
)) = N
8620 Error_Msg_Sloc
:= Sloc
(Component_Clause
(Comp
));
8621 Error_Msg_N
("component clause previously given#", CC
);
8625 Rep1
: constant Node_Id
:= Component_Clause
(Comp
);
8627 if Intval
(Position
(Rep1
)) /=
8628 Intval
(Position
(CC
))
8629 or else Intval
(First_Bit
(Rep1
)) /=
8630 Intval
(First_Bit
(CC
))
8631 or else Intval
(Last_Bit
(Rep1
)) /=
8632 Intval
(Last_Bit
(CC
))
8635 ("component clause inconsistent with "
8636 & "representation of ancestor", CC
);
8638 elsif Warn_On_Redundant_Constructs
then
8640 ("?r?redundant confirming component clause "
8641 & "for component!", CC
);
8646 -- Normal case where this is the first component clause we
8647 -- have seen for this entity, so set it up properly.
8650 -- Make reference for field in record rep clause and set
8651 -- appropriate entity field in the field identifier.
8654 (Comp
, Component_Name
(CC
), Set_Ref
=> False);
8655 Set_Entity_With_Checks
(Component_Name
(CC
), Comp
);
8657 -- Update Fbit and Lbit to the actual bit number
8659 Fbit
:= Fbit
+ UI_From_Int
(SSU
) * Posit
;
8660 Lbit
:= Lbit
+ UI_From_Int
(SSU
) * Posit
;
8662 if Has_Size_Clause
(Rectype
)
8663 and then RM_Size
(Rectype
) <= Lbit
8665 Error_Msg_Uint_1
:= RM_Size
(Rectype
);
8666 Error_Msg_Uint_2
:= Lbit
+ 1;
8667 Error_Msg_N
("bit number out of range of specified "
8668 & "size (expected ^, got ^)",
8671 Set_Component_Clause
(Comp
, CC
);
8672 Set_Component_Bit_Offset
(Comp
, Fbit
);
8673 Set_Esize
(Comp
, 1 + (Lbit
- Fbit
));
8674 Set_Normalized_First_Bit
(Comp
, Fbit
mod SSU
);
8675 Set_Normalized_Position
(Comp
, Fbit
/ SSU
);
8677 if Warn_On_Overridden_Size
8678 and then Has_Size_Clause
(Etype
(Comp
))
8679 and then RM_Size
(Etype
(Comp
)) /= Esize
(Comp
)
8682 ("?.s?component size overrides size clause for&",
8683 Component_Name
(CC
), Etype
(Comp
));
8687 (Component_Name
(CC
),
8693 (Comp
, First_Node
(CC
), "component clause", Biased
);
8695 -- This information is also set in the corresponding
8696 -- component of the base type, found by accessing the
8697 -- Original_Record_Component link if it is present.
8699 Ocomp
:= Original_Record_Component
(Comp
);
8701 if Present
(Ocomp
) and then Ocomp
/= Comp
then
8702 Set_Component_Clause
(Ocomp
, CC
);
8703 Set_Component_Bit_Offset
(Ocomp
, Fbit
);
8704 Set_Esize
(Ocomp
, 1 + (Lbit
- Fbit
));
8705 Set_Normalized_First_Bit
(Ocomp
, Fbit
mod SSU
);
8706 Set_Normalized_Position
(Ocomp
, Fbit
/ SSU
);
8708 -- Note: we don't use Set_Biased here, because we
8709 -- already gave a warning above if needed, and we
8710 -- would get a duplicate for the same name here.
8712 Set_Has_Biased_Representation
8713 (Ocomp
, Has_Biased_Representation
(Comp
));
8716 if Esize
(Comp
) < 0 then
8717 Error_Msg_N
("component size is negative", CC
);
8728 -- Check missing components if Complete_Representation pragma appeared
8730 if Present
(CR_Pragma
) then
8731 Comp
:= First_Component_Or_Discriminant
(Rectype
);
8732 while Present
(Comp
) loop
8733 if No
(Component_Clause
(Comp
)) then
8735 ("missing component clause for &", CR_Pragma
, Comp
);
8738 Next_Component_Or_Discriminant
(Comp
);
8741 -- Give missing components warning if required
8743 elsif Warn_On_Unrepped_Components
then
8745 Num_Repped_Components
: Nat
:= 0;
8746 Num_Unrepped_Components
: Nat
:= 0;
8749 -- First count number of repped and unrepped components
8751 Comp
:= First_Component_Or_Discriminant
(Rectype
);
8752 while Present
(Comp
) loop
8753 if Present
(Component_Clause
(Comp
)) then
8754 Num_Repped_Components
:= Num_Repped_Components
+ 1;
8756 Num_Unrepped_Components
:= Num_Unrepped_Components
+ 1;
8759 Next_Component_Or_Discriminant
(Comp
);
8762 -- We are only interested in the case where there is at least one
8763 -- unrepped component, and at least half the components have rep
8764 -- clauses. We figure that if less than half have them, then the
8765 -- partial rep clause is really intentional. If the component
8766 -- type has no underlying type set at this point (as for a generic
8767 -- formal type), we don't know enough to give a warning on the
8770 if Num_Unrepped_Components
> 0
8771 and then Num_Unrepped_Components
< Num_Repped_Components
8773 Comp
:= First_Component_Or_Discriminant
(Rectype
);
8774 while Present
(Comp
) loop
8775 if No
(Component_Clause
(Comp
))
8776 and then Comes_From_Source
(Comp
)
8777 and then Present
(Underlying_Type
(Etype
(Comp
)))
8778 and then (Is_Scalar_Type
(Underlying_Type
(Etype
(Comp
)))
8779 or else Size_Known_At_Compile_Time
8780 (Underlying_Type
(Etype
(Comp
))))
8781 and then not Has_Warnings_Off
(Rectype
)
8783 -- Ignore discriminant in unchecked union, since it is
8784 -- not there, and cannot have a component clause.
8786 and then (not Is_Unchecked_Union
(Rectype
)
8787 or else Ekind
(Comp
) /= E_Discriminant
)
8789 Error_Msg_Sloc
:= Sloc
(Comp
);
8791 ("?.c?no component clause given for & declared #",
8795 Next_Component_Or_Discriminant
(Comp
);
8800 end Analyze_Record_Representation_Clause
;
8802 -------------------------------------
8803 -- Build_Discrete_Static_Predicate --
8804 -------------------------------------
8806 procedure Build_Discrete_Static_Predicate
8811 Loc
: constant Source_Ptr
:= Sloc
(Expr
);
8813 Btyp
: constant Entity_Id
:= Base_Type
(Typ
);
8815 BLo
: constant Uint
:= Expr_Value
(Type_Low_Bound
(Btyp
));
8816 BHi
: constant Uint
:= Expr_Value
(Type_High_Bound
(Btyp
));
8817 -- Low bound and high bound value of base type of Typ
8821 -- Bounds for constructing the static predicate. We use the bound of the
8822 -- subtype if it is static, otherwise the corresponding base type bound.
8823 -- Note: a non-static subtype can have a static predicate.
8828 -- One entry in a Rlist value, a single REnt (range entry) value denotes
8829 -- one range from Lo to Hi. To represent a single value range Lo = Hi =
8832 type RList
is array (Nat
range <>) of REnt
;
8833 -- A list of ranges. The ranges are sorted in increasing order, and are
8834 -- disjoint (there is a gap of at least one value between each range in
8835 -- the table). A value is in the set of ranges in Rlist if it lies
8836 -- within one of these ranges.
8838 False_Range
: constant RList
:=
8839 RList
'(1 .. 0 => REnt'(No_Uint
, No_Uint
));
8840 -- An empty set of ranges represents a range list that can never be
8841 -- satisfied, since there are no ranges in which the value could lie,
8842 -- so it does not lie in any of them. False_Range is a canonical value
8843 -- for this empty set, but general processing should test for an Rlist
8844 -- with length zero (see Is_False predicate), since other null ranges
8845 -- may appear which must be treated as False.
8847 True_Range
: constant RList
:= RList
'(1 => REnt'(BLo
, BHi
));
8848 -- Range representing True, value must be in the base range
8850 function "and" (Left
: RList
; Right
: RList
) return RList
;
8851 -- And's together two range lists, returning a range list. This is a set
8852 -- intersection operation.
8854 function "or" (Left
: RList
; Right
: RList
) return RList
;
8855 -- Or's together two range lists, returning a range list. This is a set
8858 function "not" (Right
: RList
) return RList
;
8859 -- Returns complement of a given range list, i.e. a range list
8860 -- representing all the values in TLo .. THi that are not in the input
8863 function Build_Val
(V
: Uint
) return Node_Id
;
8864 -- Return an analyzed N_Identifier node referencing this value, suitable
8865 -- for use as an entry in the Static_Discrete_Predicate list. This node
8866 -- is typed with the base type.
8868 function Build_Range
(Lo
: Uint
; Hi
: Uint
) return Node_Id
;
8869 -- Return an analyzed N_Range node referencing this range, suitable for
8870 -- use as an entry in the Static_Discrete_Predicate list. This node is
8871 -- typed with the base type.
8875 Static
: access Boolean) return RList
;
8876 -- This is a recursive routine that converts the given expression into a
8877 -- list of ranges, suitable for use in building the static predicate.
8878 -- Static.all will be set to False if the expression is found to be non
8879 -- static. Note that Static.all should be set to True by the caller.
8881 function Is_False
(R
: RList
) return Boolean;
8882 pragma Inline
(Is_False
);
8883 -- Returns True if the given range list is empty, and thus represents a
8884 -- False list of ranges that can never be satisfied.
8886 function Is_True
(R
: RList
) return Boolean;
8887 -- Returns True if R trivially represents the True predicate by having a
8888 -- single range from BLo to BHi.
8890 function Is_Type_Ref
(N
: Node_Id
) return Boolean;
8891 pragma Inline
(Is_Type_Ref
);
8892 -- Returns if True if N is a reference to the type for the predicate in
8893 -- the expression (i.e. if it is an identifier whose Chars field matches
8894 -- the Nam given in the call). N must not be parenthesized, if the type
8895 -- name appears in parens, this routine will return False.
8897 function Lo_Val
(N
: Node_Id
) return Uint
;
8898 -- Given an entry from a Static_Discrete_Predicate list that is either
8899 -- a static expression or static range, gets either the expression value
8900 -- or the low bound of the range.
8902 function Hi_Val
(N
: Node_Id
) return Uint
;
8903 -- Given an entry from a Static_Discrete_Predicate list that is either
8904 -- a static expression or static range, gets either the expression value
8905 -- or the high bound of the range.
8907 function Membership_Entry
8908 (N
: Node_Id
; Static
: access Boolean) return RList
;
8909 -- Given a single membership entry (range, value, or subtype), returns
8910 -- the corresponding range list. Set Static.all to False if not static.
8912 function Membership_Entries
8913 (N
: Node_Id
; Static
: access Boolean) return RList
;
8914 -- Given an element on an alternatives list of a membership operation,
8915 -- returns the range list corresponding to this entry and all following
8916 -- entries (i.e. returns the "or" of this list of values).
8917 -- Set Static.all to False if not static.
8921 Static
: access Boolean) return RList
;
8922 -- Given a type, if it has a static predicate, then set Result to the
8923 -- predicate as a range list, otherwise set Static.all to False.
8925 procedure Warn_If_Test_Ineffective
(REntry
: REnt
; N
: Node_Id
);
8926 -- Issue a warning if REntry includes only values that are
8927 -- outside the range TLo .. THi.
8933 function "and" (Left
: RList
; Right
: RList
) return RList
is
8935 -- First range of result
8937 SLeft
: Nat
:= Left
'First;
8938 -- Start of rest of left entries
8940 SRight
: Nat
:= Right
'First;
8941 -- Start of rest of right entries
8944 -- If either range is True, return the other
8946 if Is_True
(Left
) then
8948 elsif Is_True
(Right
) then
8952 -- If either range is False, return False
8954 if Is_False
(Left
) or else Is_False
(Right
) then
8958 -- Loop to remove entries at start that are disjoint, and thus just
8959 -- get discarded from the result entirely.
8962 -- If no operands left in either operand, result is false
8964 if SLeft
> Left
'Last or else SRight
> Right
'Last then
8967 -- Discard first left operand entry if disjoint with right
8969 elsif Left
(SLeft
).Hi
< Right
(SRight
).Lo
then
8972 -- Discard first right operand entry if disjoint with left
8974 elsif Right
(SRight
).Hi
< Left
(SLeft
).Lo
then
8975 SRight
:= SRight
+ 1;
8977 -- Otherwise we have an overlapping entry
8984 -- Now we have two non-null operands, and first entries overlap. The
8985 -- first entry in the result will be the overlapping part of these
8988 FEnt
:= REnt
'(Lo => UI_Max (Left (SLeft).Lo, Right (SRight).Lo),
8989 Hi => UI_Min (Left (SLeft).Hi, Right (SRight).Hi));
8991 -- Now we can remove the entry that ended at a lower value, since its
8992 -- contribution is entirely contained in Fent.
8994 if Left (SLeft).Hi <= Right (SRight).Hi then
8997 SRight := SRight + 1;
9000 -- Compute result by concatenating this first entry with the "and" of
9001 -- the remaining parts of the left and right operands. Note that if
9002 -- either of these is empty, "and" will yield empty, so that we will
9003 -- end up with just Fent, which is what we want in that case.
9006 FEnt & (Left (SLeft .. Left'Last) and Right (SRight .. Right'Last));
9013 function "not" (Right : RList) return RList is
9015 -- Return True if False range
9017 if Is_False (Right) then
9021 -- Return False if True range
9023 if Is_True (Right) then
9027 -- Here if not trivial case
9030 Result : RList (1 .. Right'Length + 1);
9031 -- May need one more entry for gap at beginning and end
9034 -- Number of entries stored in Result
9039 if Right (Right'First).Lo > TLo then
9041 Result (Count) := REnt'(TLo
, Right
(Right
'First).Lo
- 1);
9044 -- Gaps between ranges
9046 for J
in Right
'First .. Right
'Last - 1 loop
9048 Result
(Count
) := REnt
'(Right (J).Hi + 1, Right (J + 1).Lo - 1);
9053 if Right (Right'Last).Hi < THi then
9055 Result (Count) := REnt'(Right
(Right
'Last).Hi
+ 1, THi
);
9058 return Result
(1 .. Count
);
9066 function "or" (Left
: RList
; Right
: RList
) return RList
is
9068 -- First range of result
9070 SLeft
: Nat
:= Left
'First;
9071 -- Start of rest of left entries
9073 SRight
: Nat
:= Right
'First;
9074 -- Start of rest of right entries
9077 -- If either range is True, return True
9079 if Is_True
(Left
) or else Is_True
(Right
) then
9083 -- If either range is False (empty), return the other
9085 if Is_False
(Left
) then
9087 elsif Is_False
(Right
) then
9091 -- Initialize result first entry from left or right operand depending
9092 -- on which starts with the lower range.
9094 if Left
(SLeft
).Lo
< Right
(SRight
).Lo
then
9095 FEnt
:= Left
(SLeft
);
9098 FEnt
:= Right
(SRight
);
9099 SRight
:= SRight
+ 1;
9102 -- This loop eats ranges from left and right operands that are
9103 -- contiguous with the first range we are gathering.
9106 -- Eat first entry in left operand if contiguous or overlapped by
9107 -- gathered first operand of result.
9109 if SLeft
<= Left
'Last
9110 and then Left
(SLeft
).Lo
<= FEnt
.Hi
+ 1
9112 FEnt
.Hi
:= UI_Max
(FEnt
.Hi
, Left
(SLeft
).Hi
);
9115 -- Eat first entry in right operand if contiguous or overlapped by
9116 -- gathered right operand of result.
9118 elsif SRight
<= Right
'Last
9119 and then Right
(SRight
).Lo
<= FEnt
.Hi
+ 1
9121 FEnt
.Hi
:= UI_Max
(FEnt
.Hi
, Right
(SRight
).Hi
);
9122 SRight
:= SRight
+ 1;
9124 -- All done if no more entries to eat
9131 -- Obtain result as the first entry we just computed, concatenated
9132 -- to the "or" of the remaining results (if one operand is empty,
9133 -- this will just concatenate with the other
9136 FEnt
& (Left
(SLeft
.. Left
'Last) or Right
(SRight
.. Right
'Last));
9143 function Build_Range
(Lo
: Uint
; Hi
: Uint
) return Node_Id
is
9148 Low_Bound
=> Build_Val
(Lo
),
9149 High_Bound
=> Build_Val
(Hi
));
9150 Set_Etype
(Result
, Btyp
);
9151 Set_Analyzed
(Result
);
9159 function Build_Val
(V
: Uint
) return Node_Id
is
9163 if Is_Enumeration_Type
(Typ
) then
9164 Result
:= Get_Enum_Lit_From_Pos
(Typ
, V
, Loc
);
9166 Result
:= Make_Integer_Literal
(Loc
, V
);
9169 Set_Etype
(Result
, Btyp
);
9170 Set_Is_Static_Expression
(Result
);
9171 Set_Analyzed
(Result
);
9181 Static
: access Boolean) return RList
9185 Val_Bearer
: Node_Id
;
9188 -- Static expression can only be true or false
9190 if Is_OK_Static_Expression
(Exp
) then
9191 if Expr_Value
(Exp
) = 0 then
9198 -- Otherwise test node type
9209 return Get_RList
(Left_Opnd
(Exp
), Static
)
9211 Get_RList
(Right_Opnd
(Exp
), Static
);
9218 return Get_RList
(Left_Opnd
(Exp
), Static
)
9220 Get_RList
(Right_Opnd
(Exp
), Static
);
9225 return not Get_RList
(Right_Opnd
(Exp
), Static
);
9227 -- Comparisons of type with static value
9229 when N_Op_Compare
=>
9231 -- Type is left operand
9233 if Is_Type_Ref
(Left_Opnd
(Exp
))
9234 and then Is_OK_Static_Expression
(Right_Opnd
(Exp
))
9236 Val_Bearer
:= Right_Opnd
(Exp
);
9238 -- Typ is right operand
9240 elsif Is_Type_Ref
(Right_Opnd
(Exp
))
9241 and then Is_OK_Static_Expression
(Left_Opnd
(Exp
))
9243 Val_Bearer
:= Left_Opnd
(Exp
);
9245 -- Invert sense of comparison
9248 when N_Op_Gt
=> Op
:= N_Op_Lt
;
9249 when N_Op_Lt
=> Op
:= N_Op_Gt
;
9250 when N_Op_Ge
=> Op
:= N_Op_Le
;
9251 when N_Op_Le
=> Op
:= N_Op_Ge
;
9252 when others => null;
9255 -- Other cases are non-static
9258 Static
.all := False;
9262 Val
:= Expr_Value
(Val_Bearer
);
9264 -- Construct range according to comparison operation
9271 REntry
:= (Val
, Val
);
9274 REntry
:= (Val
, THi
);
9277 REntry
:= (Val
+ 1, THi
);
9280 REntry
:= (TLo
, Val
);
9283 REntry
:= (TLo
, Val
- 1);
9286 Warn_If_Test_Ineffective
((Val
, Val
), Val_Bearer
);
9287 return RList
'(REnt'(TLo
, Val
- 1),
9288 REnt
'(Val + 1, THi));
9291 raise Program_Error;
9294 Warn_If_Test_Ineffective (REntry, Val_Bearer);
9295 return RList'(1 => REntry
);
9301 if not Is_Type_Ref
(Left_Opnd
(Exp
)) then
9302 Static
.all := False;
9306 if Present
(Right_Opnd
(Exp
)) then
9307 return Membership_Entry
(Right_Opnd
(Exp
), Static
);
9309 return Membership_Entries
9310 (First
(Alternatives
(Exp
)), Static
);
9313 -- Negative membership (NOT IN)
9316 if not Is_Type_Ref
(Left_Opnd
(Exp
)) then
9317 Static
.all := False;
9321 if Present
(Right_Opnd
(Exp
)) then
9322 return not Membership_Entry
(Right_Opnd
(Exp
), Static
);
9324 return not Membership_Entries
9325 (First
(Alternatives
(Exp
)), Static
);
9328 -- Function call, may be call to static predicate
9330 when N_Function_Call
=>
9331 if Is_Entity_Name
(Name
(Exp
)) then
9333 Ent
: constant Entity_Id
:= Entity
(Name
(Exp
));
9335 if Is_Predicate_Function
(Ent
) then
9336 return Stat_Pred
(Etype
(First_Formal
(Ent
)), Static
);
9341 -- Other function call cases are non-static
9343 Static
.all := False;
9346 -- Qualified expression, dig out the expression
9348 when N_Qualified_Expression
=>
9349 return Get_RList
(Expression
(Exp
), Static
);
9351 when N_Case_Expression
=>
9358 if not Is_Entity_Name
(Expression
(Expr
))
9359 or else Etype
(Expression
(Expr
)) /= Typ
9362 ("expression must denote subtype", Expression
(Expr
));
9366 -- Collect discrete choices in all True alternatives
9368 Choices
:= New_List
;
9369 Alt
:= First
(Alternatives
(Exp
));
9370 while Present
(Alt
) loop
9371 Dep
:= Expression
(Alt
);
9373 if not Is_OK_Static_Expression
(Dep
) then
9374 Static
.all := False;
9377 elsif Is_True
(Expr_Value
(Dep
)) then
9378 Append_List_To
(Choices
,
9379 New_Copy_List
(Discrete_Choices
(Alt
)));
9385 return Membership_Entries
(First
(Choices
), Static
);
9388 -- Expression with actions: if no actions, dig out expression
9390 when N_Expression_With_Actions
=>
9391 if Is_Empty_List
(Actions
(Exp
)) then
9392 return Get_RList
(Expression
(Exp
), Static
);
9394 Static
.all := False;
9401 return (Get_RList
(Left_Opnd
(Exp
), Static
)
9402 and not Get_RList
(Right_Opnd
(Exp
), Static
))
9403 or (Get_RList
(Right_Opnd
(Exp
), Static
)
9404 and not Get_RList
(Left_Opnd
(Exp
), Static
));
9406 -- Any other node type is non-static
9409 Static
.all := False;
9418 function Hi_Val
(N
: Node_Id
) return Uint
is
9420 if Is_OK_Static_Expression
(N
) then
9421 return Expr_Value
(N
);
9423 pragma Assert
(Nkind
(N
) = N_Range
);
9424 return Expr_Value
(High_Bound
(N
));
9432 function Is_False
(R
: RList
) return Boolean is
9434 return R
'Length = 0;
9441 function Is_True
(R
: RList
) return Boolean is
9444 and then R
(R
'First).Lo
= BLo
9445 and then R
(R
'First).Hi
= BHi
;
9452 function Is_Type_Ref
(N
: Node_Id
) return Boolean is
9454 return Nkind
(N
) = N_Identifier
9455 and then Chars
(N
) = Nam
9456 and then Paren_Count
(N
) = 0;
9463 function Lo_Val
(N
: Node_Id
) return Uint
is
9465 if Is_OK_Static_Expression
(N
) then
9466 return Expr_Value
(N
);
9468 pragma Assert
(Nkind
(N
) = N_Range
);
9469 return Expr_Value
(Low_Bound
(N
));
9473 ------------------------
9474 -- Membership_Entries --
9475 ------------------------
9477 function Membership_Entries
9478 (N
: Node_Id
; Static
: access Boolean) return RList
is
9480 if No
(Next
(N
)) then
9481 return Membership_Entry
(N
, Static
);
9483 return Membership_Entry
(N
, Static
)
9484 or Membership_Entries
(Next
(N
), Static
);
9486 end Membership_Entries
;
9488 ----------------------
9489 -- Membership_Entry --
9490 ----------------------
9492 function Membership_Entry
9493 (N
: Node_Id
; Static
: access Boolean) return RList
9502 if Nkind
(N
) = N_Range
then
9503 if not Is_OK_Static_Expression
(Low_Bound
(N
))
9505 not Is_OK_Static_Expression
(High_Bound
(N
))
9507 Static
.all := False;
9510 SLo
:= Expr_Value
(Low_Bound
(N
));
9511 SHi
:= Expr_Value
(High_Bound
(N
));
9513 REntry
: constant REnt
:= (SLo
, SHi
);
9515 Warn_If_Test_Ineffective
(REntry
, N
);
9516 return RList
'(1 => REntry);
9522 elsif Nkind (N) = N_Others_Choice then
9524 Choices : constant List_Id := Others_Discrete_Choices (N);
9526 Range_List : RList (1 .. List_Length (Choices));
9529 Choice := First (Choices);
9531 for J in Range_List'Range loop
9532 Range_List (J) := REnt'(Lo_Val
(Choice
), Hi_Val
(Choice
));
9539 -- Static expression case
9541 elsif Is_OK_Static_Expression
(N
) then
9542 Val
:= Expr_Value
(N
);
9544 REntry
: constant REnt
:= (Val
, Val
);
9546 Warn_If_Test_Ineffective
(REntry
, N
);
9547 return RList
'(1 => REntry);
9550 -- Identifier (other than static expression) case
9552 else pragma Assert (Nkind (N) in N_Expanded_Name | N_Identifier);
9556 if Is_Type (Entity (N)) then
9558 -- If type has predicates, process them
9560 if Has_Predicates (Entity (N)) then
9561 return Stat_Pred (Entity (N), Static);
9563 -- For static subtype without predicates, get range
9565 elsif Is_OK_Static_Subtype (Entity (N)) then
9566 SLo := Expr_Value (Type_Low_Bound (Entity (N)));
9567 SHi := Expr_Value (Type_High_Bound (Entity (N)));
9568 return RList'(1 => REnt
'(SLo, SHi));
9570 -- Any other type makes us non-static
9573 Static.all := False;
9577 -- Any other kind of identifier in predicate (e.g. a non-static
9578 -- expression value) means this is not a static predicate.
9581 Static.all := False;
9585 end Membership_Entry;
9593 Static : access Boolean) return RList is
9595 -- Not static if type does not have static predicates
9597 if not Has_Static_Predicate (Typ) then
9598 Static.all := False;
9602 -- Otherwise we convert the predicate list to a range list
9605 Spred : constant List_Id := Static_Discrete_Predicate (Typ);
9606 Result : RList (1 .. List_Length (Spred));
9610 P := First (Static_Discrete_Predicate (Typ));
9611 for J in Result'Range loop
9612 Result (J) := REnt'(Lo_Val
(P
), Hi_Val
(P
));
9620 procedure Warn_If_Test_Ineffective
(REntry
: REnt
; N
: Node_Id
) is
9622 procedure IPT_Warning
(Msg
: String);
9628 procedure IPT_Warning
(Msg
: String) is
9630 Error_Msg_N
("ineffective predicate test " & Msg
& "?_s?", N
);
9633 -- Start of processing for Warn_If_Test_Ineffective
9636 -- Do nothing if warning disabled
9638 if not Warn_On_Ineffective_Predicate_Test
then
9641 -- skip null-range corner cases
9643 elsif REntry
.Lo
> REntry
.Hi
or else TLo
> THi
then
9646 -- warn if no overlap between subtype bounds and the given range
9648 elsif REntry
.Lo
> THi
or else REntry
.Hi
< TLo
then
9649 Error_Msg_Uint_1
:= REntry
.Lo
;
9650 if REntry
.Lo
/= REntry
.Hi
then
9651 Error_Msg_Uint_2
:= REntry
.Hi
;
9652 IPT_Warning
("range: ^ .. ^");
9653 elsif Is_Enumeration_Type
(Typ
) and then
9654 Nkind
(N
) in N_Identifier | N_Expanded_Name
9656 IPT_Warning
("value: &");
9658 IPT_Warning
("value: ^");
9661 end Warn_If_Test_Ineffective
;
9663 -- Start of processing for Build_Discrete_Static_Predicate
9666 -- Establish bounds for the predicate
9668 if Compile_Time_Known_Value
(Type_Low_Bound
(Typ
)) then
9669 TLo
:= Expr_Value
(Type_Low_Bound
(Typ
));
9674 if Compile_Time_Known_Value
(Type_High_Bound
(Typ
)) then
9675 THi
:= Expr_Value
(Type_High_Bound
(Typ
));
9680 -- Analyze the expression to see if it is a static predicate
9683 Static
: aliased Boolean := True;
9684 Ranges
: constant RList
:= Get_RList
(Expr
, Static
'Access);
9685 -- Range list from expression if it is static
9690 -- If non-static, return doing nothing
9696 -- Convert range list into a form for the static predicate. In the
9697 -- Ranges array, we just have raw ranges, these must be converted
9698 -- to properly typed and analyzed static expressions or range nodes.
9700 -- Note: here we limit ranges to the ranges of the subtype, so that
9701 -- a predicate is always false for values outside the subtype. That
9702 -- seems fine, such values are invalid anyway, and considering them
9703 -- to fail the predicate seems allowed and friendly, and furthermore
9704 -- simplifies processing for case statements and loops.
9708 for J
in Ranges
'Range loop
9710 Lo
: Uint
:= Ranges
(J
).Lo
;
9711 Hi
: Uint
:= Ranges
(J
).Hi
;
9714 -- Ignore completely out of range entry
9716 if Hi
< TLo
or else Lo
> THi
then
9719 -- Otherwise process entry
9722 -- Adjust out of range value to subtype range
9732 -- Convert range into required form
9734 Append_To
(Plist
, Build_Range
(Lo
, Hi
));
9739 -- Processing was successful and all entries were static, so now we
9740 -- can store the result as the predicate list.
9742 Set_Static_Discrete_Predicate
(Typ
, Plist
);
9744 -- Within a generic the predicate functions themselves need not
9747 if Inside_A_Generic
then
9751 -- The processing for static predicates put the expression into
9752 -- canonical form as a series of ranges. It also eliminated
9753 -- duplicates and collapsed and combined ranges. We might as well
9754 -- replace the alternatives list of the right operand of the
9755 -- membership test with the static predicate list, which will
9756 -- usually be more efficient.
9759 New_Alts
: constant List_Id
:= New_List
;
9764 Old_Node
:= First
(Plist
);
9765 while Present
(Old_Node
) loop
9766 New_Node
:= New_Copy
(Old_Node
);
9768 if Nkind
(New_Node
) = N_Range
then
9769 Set_Low_Bound
(New_Node
, New_Copy
(Low_Bound
(Old_Node
)));
9770 Set_High_Bound
(New_Node
, New_Copy
(High_Bound
(Old_Node
)));
9773 Append_To
(New_Alts
, New_Node
);
9777 -- If empty list, replace by False
9779 if Is_Empty_List
(New_Alts
) then
9780 Rewrite
(Expr
, New_Occurrence_Of
(Standard_False
, Loc
));
9782 -- Else replace by set membership test
9787 Left_Opnd
=> Make_Identifier
(Loc
, Nam
),
9788 Right_Opnd
=> Empty
,
9789 Alternatives
=> New_Alts
));
9791 -- Resolve new expression in function context
9793 Push_Scope
(Predicate_Function
(Typ
));
9794 Install_Formals
(Predicate_Function
(Typ
));
9795 Analyze_And_Resolve
(Expr
, Standard_Boolean
);
9800 end Build_Discrete_Static_Predicate
;
9802 --------------------------------
9803 -- Build_Export_Import_Pragma --
9804 --------------------------------
9806 function Build_Export_Import_Pragma
9808 Id
: Entity_Id
) return Node_Id
9810 Asp_Id
: constant Aspect_Id
:= Get_Aspect_Id
(Asp
);
9811 Expr
: constant Node_Id
:= Expression
(Asp
);
9812 Loc
: constant Source_Ptr
:= Sloc
(Asp
);
9823 Create_Pragma
: Boolean := False;
9824 -- This flag is set when the aspect form is such that it warrants the
9825 -- creation of a corresponding pragma.
9828 if Present
(Expr
) then
9829 if Error_Posted
(Expr
) then
9832 elsif Is_True
(Expr_Value
(Expr
)) then
9833 Create_Pragma
:= True;
9836 -- Otherwise the aspect defaults to True
9839 Create_Pragma
:= True;
9842 -- Nothing to do when the expression is False or is erroneous
9844 if not Create_Pragma
then
9848 -- Obtain all interfacing aspects that apply to the related entity
9850 Get_Interfacing_Aspects
9854 Expo_Asp
=> Dummy_1
,
9860 -- Handle the convention argument
9862 if Present
(Conv
) then
9863 Conv_Arg
:= New_Copy_Tree
(Expression
(Conv
));
9865 -- Assume convention "Ada' when aspect Convention is missing
9868 Conv_Arg
:= Make_Identifier
(Loc
, Name_Ada
);
9872 Make_Pragma_Argument_Association
(Loc
,
9873 Chars
=> Name_Convention
,
9874 Expression
=> Conv_Arg
));
9876 -- Handle the entity argument
9879 Make_Pragma_Argument_Association
(Loc
,
9880 Chars
=> Name_Entity
,
9881 Expression
=> New_Occurrence_Of
(Id
, Loc
)));
9883 -- Handle the External_Name argument
9885 if Present
(EN
) then
9887 Make_Pragma_Argument_Association
(Loc
,
9888 Chars
=> Name_External_Name
,
9889 Expression
=> New_Copy_Tree
(Expression
(EN
))));
9892 -- Handle the Link_Name argument
9894 if Present
(LN
) then
9896 Make_Pragma_Argument_Association
(Loc
,
9897 Chars
=> Name_Link_Name
,
9898 Expression
=> New_Copy_Tree
(Expression
(LN
))));
9902 -- pragma Export/Import
9903 -- (Convention => <Conv>/Ada,
9905 -- [External_Name => <EN>,]
9906 -- [Link_Name => <LN>]);
9910 Pragma_Identifier
=>
9911 Make_Identifier
(Loc
, Chars
(Identifier
(Asp
))),
9912 Pragma_Argument_Associations
=> Args
);
9914 -- Decorate the relevant aspect and the pragma
9916 Set_Aspect_Rep_Item
(Asp
, Prag
);
9918 Set_Corresponding_Aspect
(Prag
, Asp
);
9919 Set_From_Aspect_Specification
(Prag
);
9920 Set_Parent
(Prag
, Asp
);
9922 if Asp_Id
= Aspect_Import
and then Is_Subprogram
(Id
) then
9923 Set_Import_Pragma
(Id
, Prag
);
9927 end Build_Export_Import_Pragma
;
9929 ------------------------------
9930 -- Build_Predicate_Function --
9931 ------------------------------
9933 -- The function constructed here has the form:
9935 -- function typPredicate (Ixxx : typ) return Boolean is
9938 -- typ1Predicate (typ1 (Ixxx))
9939 -- and then typ2Predicate (typ2 (Ixxx))
9941 -- and then exp1 and then exp2 and then ...;
9942 -- end typPredicate;
9944 -- If Predicate_Function_Needs_Membership_Parameter is true, then this
9945 -- function takes an additional boolean parameter; the parameter
9946 -- indicates whether the predicate evaluation is part of a membership
9947 -- test. This parameter is used in two cases: 1) It is passed along
9948 -- if another predicate function is called and that predicate function
9949 -- expects to be passed a boolean parameter. 2) If the Predicate_Failure
9950 -- aspect is directly specified for typ, then we replace the return
9951 -- expression described above with
9952 -- (if <expression described above> then True
9953 -- elsif For_Membership_Test then False
9954 -- else (raise Assertion_Error
9955 -- with <Predicate_Failure expression>))
9956 -- Here exp1, and exp2 are expressions from Predicate pragmas. Note that
9957 -- this is the point at which these expressions get analyzed, providing the
9958 -- required delay, and typ1, typ2, are entities from which predicates are
9959 -- inherited. Note that we do NOT generate Check pragmas, that's because we
9960 -- use this function even if checks are off, e.g. for membership tests.
9962 -- Note that the inherited predicates are evaluated first, as required by
9965 -- Note that Sem_Eval.Real_Or_String_Static_Predicate_Matches depends on
9966 -- the form of this return expression.
9968 -- WARNING: This routine manages Ghost regions. Return statements must be
9969 -- replaced by gotos which jump to the end of the routine and restore the
9972 procedure Build_Predicate_Function
(Typ
: Entity_Id
; N
: Node_Id
) is
9973 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
9975 Saved_GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
9976 Saved_IGR
: constant Node_Id
:= Ignored_Ghost_Region
;
9977 -- Save the Ghost-related attributes to restore on exit
9980 -- This is the expression for the result of the function. It is
9981 -- built by connecting the component predicates with AND THEN.
9983 Object_Name
: Name_Id
;
9984 -- Name for argument of Predicate procedure. Note that we use the same
9985 -- name for both predicate functions. That way the reference within the
9986 -- predicate expression is the same in both functions.
9988 Object_Entity
: Entity_Id
;
9989 -- Entity for argument of Predicate procedure
9992 -- The function declaration
9997 Restore_Scope
: Boolean;
9998 -- True if the current scope must be restored on exit
10000 Ancestor_Predicate_Function_Called
: Boolean := False;
10001 -- Does this predicate function include a call to the
10002 -- predication function of an ancestor subtype?
10004 procedure Add_Condition
(Cond
: Node_Id
);
10005 -- Append Cond to Expr using "and then" (or just copy Cond to Expr if
10008 procedure Add_Predicates
;
10009 -- Appends expressions for any Predicate pragmas in the rep item chain
10010 -- Typ to Expr. Note that we look only at items for this exact entity.
10011 -- Inheritance of predicates for the parent type is done by calling the
10012 -- Predicate_Function of the parent type, using Add_Call above.
10014 procedure Add_Call
(T
: Entity_Id
);
10015 -- Includes a call to the predicate function for type T in Expr if
10016 -- Predicate_Function (T) is non-empty.
10018 procedure Replace_Current_Instance_References
10019 (N
: Node_Id
; Typ
, New_Entity
: Entity_Id
);
10020 -- Replace all references to Typ in the tree rooted at N with
10021 -- references to Param. [New_Entity will be a formal parameter of a
10022 -- predicate function.]
10028 procedure Add_Call
(T
: Entity_Id
) is
10032 if Present
(Predicate_Function
(T
)) then
10033 pragma Assert
(Has_Predicates
(Typ
));
10035 -- Build the call to the predicate function of T. The type may be
10036 -- derived, so use an unchecked conversion for the actual.
10039 Dynamic_Mem
: Node_Id
:= Empty
;
10040 Second_Formal
: constant Entity_Id
:=
10041 Next_Entity
(Object_Entity
);
10043 -- Some predicate functions require a second parameter;
10044 -- If one predicate function calls another and the second
10045 -- requires two parameters, then the first should also
10046 -- take two parameters (so that the first function has
10047 -- something to pass to the second function).
10048 if Predicate_Function_Needs_Membership_Parameter
(T
) then
10049 pragma Assert
(Present
(Second_Formal
));
10050 Dynamic_Mem
:= New_Occurrence_Of
(Second_Formal
, Loc
);
10054 Make_Predicate_Call
10057 Unchecked_Convert_To
(T
,
10058 Make_Identifier
(Loc
, Object_Name
)),
10059 Dynamic_Mem
=> Dynamic_Mem
);
10062 -- "and"-in the call to evolving expression
10064 Add_Condition
(Exp
);
10065 Ancestor_Predicate_Function_Called
:= True;
10067 -- Output info message on inheritance if required. Note we do not
10068 -- give this information for generic actual types, since it is
10069 -- unwelcome noise in that case in instantiations. We also
10070 -- generally suppress the message in instantiations, and also
10071 -- if it involves internal names.
10073 if List_Inherited_Aspects
10074 and then not Is_Generic_Actual_Type
(Typ
)
10075 and then Instantiation_Location
(Sloc
(Typ
)) = No_Location
10076 and then not Is_Internal_Name
(Chars
(T
))
10077 and then not Is_Internal_Name
(Chars
(Typ
))
10079 Error_Msg_Sloc
:= Sloc
(Predicate_Function
(T
));
10080 Error_Msg_Node_2
:= T
;
10081 Error_Msg_N
("info: & inherits predicate from & #?.l?", Typ
);
10086 -------------------
10087 -- Add_Condition --
10088 -------------------
10090 procedure Add_Condition
(Cond
: Node_Id
) is
10092 -- This is the first predicate expression
10097 -- Otherwise concatenate to the existing predicate expressions by
10098 -- using "and then".
10102 Make_And_Then
(Loc
,
10103 Left_Opnd
=> Relocate_Node
(Expr
),
10104 Right_Opnd
=> Cond
);
10108 --------------------
10109 -- Add_Predicates --
10110 --------------------
10112 procedure Add_Predicates
is
10113 procedure Add_Predicate
(Prag
: Node_Id
);
10114 -- Concatenate the expression of predicate pragma Prag to Expr by
10115 -- using a short circuit "and then" operator.
10117 -------------------
10118 -- Add_Predicate --
10119 -------------------
10121 procedure Add_Predicate
(Prag
: Node_Id
) is
10124 Asp
: constant Node_Id
:= Corresponding_Aspect
(Prag
);
10128 -- Start of processing for Add_Predicate
10131 -- A ghost predicate is checked only when Ghost mode is enabled.
10132 -- Add a condition for the presence of a predicate to be recorded,
10133 -- which is needed to generate the corresponding predicate
10136 if Is_Ignored_Ghost_Pragma
(Prag
) then
10137 Add_Condition
(New_Occurrence_Of
(Standard_True
, Sloc
(Prag
)));
10141 -- Mark corresponding SCO as enabled
10143 Set_SCO_Pragma_Enabled
(Sloc
(Prag
));
10145 -- Extract the arguments of the pragma
10147 Arg1
:= First
(Pragma_Argument_Associations
(Prag
));
10148 Arg2
:= Next
(Arg1
);
10150 Arg1
:= Get_Pragma_Arg
(Arg1
);
10151 Arg2
:= Get_Pragma_Arg
(Arg2
);
10153 -- When the predicate pragma applies to the current type or its
10154 -- full view, replace all occurrences of the subtype name with
10155 -- references to the formal parameter of the predicate function.
10157 if Entity
(Arg1
) = Typ
10158 or else Full_View
(Entity
(Arg1
)) = Typ
10161 Arg2_Copy
: constant Node_Id
:= New_Copy_Tree
(Arg2
);
10163 Replace_Current_Instance_References
10164 (Arg2_Copy
, Typ
=> Typ
, New_Entity
=> Object_Entity
);
10166 -- If the predicate pragma comes from an aspect, replace the
10167 -- saved expression because we need the subtype references
10168 -- replaced for the calls to Preanalyze_Spec_Expression in
10169 -- Check_Aspect_At_xxx routines.
10171 if Present
(Asp
) then
10172 Set_Entity
(Identifier
(Asp
), New_Copy_Tree
(Arg2_Copy
));
10175 -- "and"-in the Arg2 condition to evolving expression
10177 Add_Condition
(Arg2_Copy
);
10186 -- Start of processing for Add_Predicates
10189 Ritem
:= First_Rep_Item
(Typ
);
10191 -- If the type is private, check whether full view has inherited
10194 if Is_Private_Type
(Typ
)
10195 and then No
(Ritem
)
10196 and then Present
(Full_View
(Typ
))
10198 Ritem
:= First_Rep_Item
(Full_View
(Typ
));
10201 while Present
(Ritem
) loop
10202 if Nkind
(Ritem
) = N_Pragma
10203 and then Pragma_Name
(Ritem
) = Name_Predicate
10205 Add_Predicate
(Ritem
);
10207 -- If the type is declared in an inner package it may be frozen
10208 -- outside of the package, and the generated pragma has not been
10209 -- analyzed yet, so capture the expression for the predicate
10210 -- function at this point.
10212 elsif Nkind
(Ritem
) = N_Aspect_Specification
10213 and then Present
(Aspect_Rep_Item
(Ritem
))
10214 and then Scope_Depth
(Scope
(Typ
)) > Scope_Depth
(Current_Scope
)
10217 Prag
: constant Node_Id
:= Aspect_Rep_Item
(Ritem
);
10220 if Nkind
(Prag
) = N_Pragma
10221 and then Pragma_Name
(Prag
) = Name_Predicate
10223 Add_Predicate
(Prag
);
10228 Next_Rep_Item
(Ritem
);
10230 end Add_Predicates
;
10232 -----------------------------------------
10233 -- Replace_Current_Instance_References --
10234 -----------------------------------------
10236 procedure Replace_Current_Instance_References
10237 (N
: Node_Id
; Typ
, New_Entity
: Entity_Id
)
10239 Root
: Node_Id
renames N
;
10241 procedure Replace_One_Reference
(N
: Node_Id
);
10242 -- Actual parameter for Replace_Type_References_Generic instance
10244 ---------------------------
10245 -- Replace_One_Reference --
10246 ---------------------------
10248 procedure Replace_One_Reference
(N
: Node_Id
) is
10249 pragma Assert
(In_Subtree
(N
, Root
=> Root
));
10251 Rewrite
(N
, New_Occurrence_Of
(New_Entity
, Sloc
(N
)));
10252 -- Use the Sloc of the usage name, not the defining name
10253 end Replace_One_Reference
;
10255 procedure Replace_Type_References
is
10256 new Replace_Type_References_Generic
(Replace_One_Reference
);
10258 Replace_Type_References
(N
, Typ
);
10259 end Replace_Current_Instance_References
;
10261 -- Start of processing for Build_Predicate_Function
10264 -- Return if already built, if type does not have predicates,
10265 -- or if type is a constructed subtype that will inherit a
10266 -- predicate function from its ancestor. In a generic context
10267 -- the predicated parent may not have a predicate function yet
10268 -- but we don't want to build a new one for the subtype. This can
10269 -- happen in an instance body which is nested within a generic
10270 -- unit, in which case Within_A_Generic may be false, SId is
10271 -- Empty, but uses of Typ will receive a predicate check in a
10272 -- context where expansion and tests are enabled.
10274 SId
:= Predicate_Function
(Typ
);
10275 if not Has_Predicates
(Typ
)
10276 or else (Present
(SId
) and then Has_Completion
(SId
))
10279 and then not Comes_From_Source
(Typ
)
10280 and then Ekind
(Typ
) in E_Array_Subtype
10282 | E_Record_Subtype_With_Private
10283 and then Present
(Predicated_Parent
(Typ
)))
10287 -- Do not generate predicate bodies within a generic unit. The
10288 -- expressions have been analyzed already, and the bodies play no role
10289 -- if not within an executable unit. However, if a static predicate is
10290 -- present it must be processed for legality checks such as case
10291 -- coverage in an expression.
10293 elsif Inside_A_Generic
10294 and then not Has_Static_Predicate_Aspect
(Typ
)
10299 -- Ensure that the declarations are added to the scope of the type
10301 if Scope
(Typ
) /= Current_Scope
then
10302 Push_Scope
(Scope
(Typ
));
10303 Restore_Scope
:= True;
10305 Restore_Scope
:= False;
10308 -- The related type may be subject to pragma Ghost. Set the mode now to
10309 -- ensure that the predicate functions are properly marked as Ghost.
10311 Set_Ghost_Mode
(Typ
);
10313 -- Prepare to construct predicate expression
10317 if Present
(SId
) then
10318 FDecl
:= Unit_Declaration_Node
(SId
);
10321 FDecl
:= Build_Predicate_Function_Declaration
(Typ
);
10322 SId
:= Defining_Entity
(FDecl
);
10325 -- Recover name of formal parameter of function that replaces references
10326 -- to the type in predicate expressions.
10329 Defining_Identifier
10330 (First
(Parameter_Specifications
(Specification
(FDecl
))));
10332 Object_Name
:= Chars
(Object_Entity
);
10334 -- Add predicates for ancestor if present. These must come before the
10335 -- ones for the current type, as required by AI12-0071-1.
10337 -- Looks like predicates aren't added for case of inheriting from
10338 -- multiple progenitors???
10343 Atyp
:= Nearest_Ancestor
(Typ
);
10345 -- The type may be private but the full view may inherit predicates
10347 if No
(Atyp
) and then Is_Private_Type
(Typ
) then
10348 Atyp
:= Nearest_Ancestor
(Full_View
(Typ
));
10351 if Present
(Atyp
) then
10356 -- Add Predicates for the current type
10360 -- Case where predicates are present
10362 if Present
(Expr
) then
10364 -- Build the main predicate function
10367 SIdB
: constant Entity_Id
:=
10368 Make_Defining_Identifier
(Loc
,
10369 Chars
=> New_External_Name
(Chars
(Typ
), "Predicate"));
10370 -- The entity for the function body
10376 Mutate_Ekind
(SIdB
, E_Function
);
10377 Set_Is_Predicate_Function
(SIdB
);
10379 -- Build function body
10382 Param_Specs
: constant List_Id
:= New_List
(
10383 Make_Parameter_Specification
(Loc
,
10384 Defining_Identifier
=>
10385 Make_Defining_Identifier
(Loc
, Object_Name
),
10387 New_Occurrence_Of
(Typ
, Loc
)));
10389 -- if Spec has 2 parameters, then body should too
10390 if Present
(Next_Entity
(Object_Entity
)) then
10391 Append
(Make_Parameter_Specification
(Loc
,
10392 Defining_Identifier
=>
10393 Make_Defining_Identifier
10394 (Loc
, Chars
(Next_Entity
(Object_Entity
))),
10396 New_Occurrence_Of
(Standard_Boolean
, Loc
)),
10401 Make_Function_Specification
(Loc
,
10402 Defining_Unit_Name
=> SIdB
,
10403 Parameter_Specifications
=> Param_Specs
,
10404 Result_Definition
=>
10405 New_Occurrence_Of
(Standard_Boolean
, Loc
));
10408 -- The Predicate_Expression attribute is used by SPARK.
10410 -- If Ancestor_Predicate_Function_Called is True, then
10411 -- we try to exclude that call to the ancestor's
10412 -- predicate function by calling Right_Opnd.
10413 -- The call is not excluded in the case where
10414 -- it is not "and"ed with anything else (so we don't have
10415 -- an N_And_Then node). This exclusion is required if the
10416 -- Predicate_Failure aspect is specified for Typ because
10417 -- in that case we are going to drop the N_And_Then node
10418 -- on the floor. Otherwise, it is a question of what is
10419 -- most convenient for SPARK.
10421 Set_Predicate_Expression
10422 (SId
, (if Ancestor_Predicate_Function_Called
10423 and then Nkind
(Expr
) = N_And_Then
10424 then Right_Opnd
(Expr
)
10428 Result_Expr
: Node_Id
:= Expr
;
10429 PF_Expr
: Node_Id
:= Predicate_Failure_Expression
10430 (Typ
, Inherited_OK
=> False);
10431 PF_Expr_Copy
: Node_Id
;
10432 Second_Formal
: constant Entity_Id
:=
10433 Next_Entity
(Object_Entity
);
10435 -- In GNATprove mode we are only interested in the predicate
10436 -- expression itself and don't want a raise expression that
10437 -- comes from the Predicate_Failure. Ditto for CodePeer.
10438 -- And an illegal Predicate_Failure aspect can lead to cases
10439 -- we want to avoid.
10441 if Present
(PF_Expr
)
10442 and then not GNATprove_Mode
10443 and then not CodePeer_Mode
10444 and then Serious_Errors_Detected
= 0
10446 pragma Assert
(Present
(Second_Formal
));
10448 -- This is an ugly hack to cope with an ugly situation.
10449 -- PF_Expr may have children whose Parent attribute
10450 -- does not point back to PF_Expr. If we pass such a
10451 -- tree to New_Copy_Tree, then it does not make a deep
10452 -- copy. But we need a deep copy. So we need to find a
10453 -- tree for which New_Copy_Tree *will* make a deep copy.
10456 function Check_Node_Parent
(Parent_Node
, Node
: Node_Id
)
10457 return Traverse_Result
;
10458 function Check_Node_Parent
(Parent_Node
, Node
: Node_Id
)
10459 return Traverse_Result
is
10461 if Parent_Node
= PF_Expr
10462 and then not Is_List_Member
(Node
)
10465 (Nkind
(PF_Expr
) = Nkind
(Parent
(Node
)));
10467 -- We need PF_Expr to be a node for which
10468 -- New_Copy_Tree will make a deep copy.
10469 PF_Expr
:= Parent
(Node
);
10473 end Check_Node_Parent
;
10474 procedure Check_Parentage
is
10475 new Traverse_Proc_With_Parent
(Check_Node_Parent
);
10477 Check_Parentage
(PF_Expr
);
10478 PF_Expr_Copy
:= New_Copy_Tree
(PF_Expr
);
10481 -- Current instance uses need to have their Entity
10482 -- fields set so that Replace_Current_Instance_References
10483 -- can find them. So we preanalyze. Just for purposes of
10484 -- calls to Is_Current_Instance during this preanalysis,
10485 -- we set the Parent field.
10486 Set_Parent
(PF_Expr_Copy
, Parent
(PF_Expr
));
10487 Preanalyze
(PF_Expr_Copy
);
10488 Set_Parent
(PF_Expr_Copy
, Empty
);
10490 Replace_Current_Instance_References
10491 (PF_Expr_Copy
, Typ
=> Typ
, New_Entity
=> Object_Entity
);
10493 if Ancestor_Predicate_Function_Called
then
10494 -- If the call to an ancestor predicate function
10495 -- returns False, we do not want to raise an
10496 -- exception here. Our Predicate_Failure aspect does
10497 -- not apply in that case. So we have to build a
10498 -- more complicated result expression:
10499 -- (if not Ancestor_Predicate_Function (...) then False
10500 -- elsif Noninherited_Predicates (...) then True
10501 -- elsif Is_Membership_Test then False
10502 -- else (raise Assertion_Error with PF text))
10505 Ancestor_Call
: constant Node_Id
:=
10506 Left_Opnd
(Result_Expr
);
10507 Local_Preds
: constant Node_Id
:=
10508 Right_Opnd
(Result_Expr
);
10511 Make_If_Expression
(Loc
,
10512 Expressions
=> New_List
(
10513 Make_Op_Not
(Loc
, Ancestor_Call
),
10514 New_Occurrence_Of
(Standard_False
, Loc
),
10515 Make_If_Expression
(Loc
,
10517 Expressions
=> New_List
(
10519 New_Occurrence_Of
(Standard_True
, Loc
),
10520 Make_If_Expression
(Loc
,
10522 Expressions
=> New_List
(
10523 New_Occurrence_Of
(Second_Formal
, Loc
),
10524 New_Occurrence_Of
(Standard_False
, Loc
),
10525 Make_Raise_Expression
(Loc
,
10526 New_Occurrence_Of
(RTE
10527 (RE_Assert_Failure
), Loc
),
10528 PF_Expr_Copy
)))))));
10532 -- Build a conditional expression:
10533 -- (if <predicate evaluates to True> then True
10534 -- elsif Is_Membership_Test then False
10535 -- else (raise Assertion_Error with PF text))
10538 Make_If_Expression
(Loc
,
10539 Expressions
=> New_List
(
10541 New_Occurrence_Of
(Standard_True
, Loc
),
10542 Make_If_Expression
(Loc
,
10544 Expressions
=> New_List
(
10545 New_Occurrence_Of
(Second_Formal
, Loc
),
10546 New_Occurrence_Of
(Standard_False
, Loc
),
10547 Make_Raise_Expression
(Loc
,
10548 New_Occurrence_Of
(RTE
10549 (RE_Assert_Failure
), Loc
),
10555 Make_Subprogram_Body
(Loc
,
10556 Specification
=> Spec
,
10557 Declarations
=> Empty_List
,
10558 Handled_Statement_Sequence
=>
10559 Make_Handled_Sequence_Of_Statements
(Loc
,
10560 Statements
=> New_List
(
10561 Make_Simple_Return_Statement
(Loc
,
10562 Expression
=> Result_Expr
))));
10565 -- The declaration has been analyzed when created, and placed
10566 -- after type declaration. Insert body itself after freeze node,
10567 -- unless subprogram declaration is already there, in which case
10568 -- body better be placed afterwards.
10570 if FDecl
= Next
(N
) then
10571 Insert_After_And_Analyze
(FDecl
, FBody
);
10573 Insert_After_And_Analyze
(N
, FBody
);
10576 -- The defining identifier of a quantified expression carries the
10577 -- scope in which the type appears, but when unnesting we need
10578 -- to indicate that its proper scope is the constructed predicate
10579 -- function. The quantified expressions have been converted into
10580 -- loops during analysis and expansion.
10583 function Reset_Quantified_Variable_Scope
10584 (N
: Node_Id
) return Traverse_Result
;
10586 procedure Reset_Quantified_Variables_Scope
is
10587 new Traverse_Proc
(Reset_Quantified_Variable_Scope
);
10589 -------------------------------------
10590 -- Reset_Quantified_Variable_Scope --
10591 -------------------------------------
10593 function Reset_Quantified_Variable_Scope
10594 (N
: Node_Id
) return Traverse_Result
is
10596 if Nkind
(N
) in N_Iterator_Specification
10597 | N_Loop_Parameter_Specification
10599 Set_Scope
(Defining_Identifier
(N
),
10600 Predicate_Function
(Typ
));
10604 end Reset_Quantified_Variable_Scope
;
10607 if Unnest_Subprogram_Mode
then
10608 Reset_Quantified_Variables_Scope
(Expr
);
10612 -- Within a generic unit, prevent a double analysis of the body
10613 -- which will not be marked analyzed yet. This will happen when
10614 -- the freeze node is created during the preanalysis of an
10615 -- expression function.
10617 if Inside_A_Generic
then
10618 Set_Analyzed
(FBody
);
10621 -- Static predicate functions are always side-effect free, and
10622 -- in most cases dynamic predicate functions are as well. Mark
10623 -- them as such whenever possible, so redundant predicate checks
10624 -- can be optimized. If there is a variable reference within the
10625 -- expression, the function is not pure.
10627 if Expander_Active
then
10629 Side_Effect_Free
(Expr
, Variable_Ref
=> True));
10630 Set_Is_Inlined
(SId
);
10634 -- See if we have a static predicate. Note that the answer may be
10635 -- yes even if we have an explicit Dynamic_Predicate present.
10642 if not Is_Scalar_Type
(Typ
) and then not Is_String_Type
(Typ
) then
10645 PS
:= Is_Predicate_Static
(Expr
, Object_Name
);
10648 -- Case where we have a predicate-static aspect
10652 -- We don't set Has_Static_Predicate_Aspect, since we can have
10653 -- any of the three cases (Predicate, Dynamic_Predicate, or
10654 -- Static_Predicate) generating a predicate with an expression
10655 -- that is predicate-static. We just indicate that we have a
10656 -- predicate that can be treated as static.
10658 Set_Has_Static_Predicate
(Typ
);
10660 -- For discrete subtype, build the static predicate list
10662 if Is_Discrete_Type
(Typ
) then
10663 Build_Discrete_Static_Predicate
(Typ
, Expr
, Object_Name
);
10665 -- If we don't get a static predicate list, it means that we
10666 -- have a case where this is not possible, most typically in
10667 -- the case where we inherit a dynamic predicate. We do not
10668 -- consider this an error, we just leave the predicate as
10669 -- dynamic. But if we do succeed in building the list, then
10670 -- we mark the predicate as static.
10672 if No
(Static_Discrete_Predicate
(Typ
)) then
10673 Set_Has_Static_Predicate
(Typ
, False);
10676 -- For real or string subtype, save predicate expression
10678 elsif Is_Real_Type
(Typ
) or else Is_String_Type
(Typ
) then
10679 Set_Static_Real_Or_String_Predicate
(Typ
, Expr
);
10682 -- Case of dynamic predicate (expression is not predicate-static)
10685 -- Again, we don't set Has_Dynamic_Predicate_Aspect, since that
10686 -- is only set if we have an explicit Dynamic_Predicate aspect
10687 -- given. Here we may simply have a Predicate aspect where the
10688 -- expression happens not to be predicate-static.
10690 -- Emit an error when the predicate is categorized as static
10691 -- but its expression is not predicate-static.
10693 -- First a little fiddling to get a nice location for the
10694 -- message. If the expression is of the form (A and then B),
10695 -- where A is an inherited predicate, then use the right
10696 -- operand for the Sloc. This avoids getting confused by a call
10697 -- to an inherited predicate with a less convenient source
10701 while Nkind
(EN
) = N_And_Then
10702 and then Nkind
(Left_Opnd
(EN
)) = N_Function_Call
10703 and then Is_Predicate_Function
10704 (Entity
(Name
(Left_Opnd
(EN
))))
10706 EN
:= Right_Opnd
(EN
);
10709 -- Now post appropriate message
10711 if Has_Static_Predicate_Aspect
(Typ
) then
10712 if Is_Scalar_Type
(Typ
) or else Is_String_Type
(Typ
) then
10714 ("expression is not predicate-static (RM 3.2.4(16-22))",
10718 ("static predicate requires scalar or string type", EN
);
10725 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
10727 if Restore_Scope
then
10730 end Build_Predicate_Function
;
10732 ------------------------------------------
10733 -- Build_Predicate_Function_Declaration --
10734 ------------------------------------------
10736 -- WARNING: This routine manages Ghost regions. Return statements must be
10737 -- replaced by gotos which jump to the end of the routine and restore the
10740 function Build_Predicate_Function_Declaration
10741 (Typ
: Entity_Id
) return Node_Id
10743 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
10745 Saved_GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
10746 Saved_IGR
: constant Node_Id
:= Ignored_Ghost_Region
;
10747 -- Save the Ghost-related attributes to restore on exit
10749 Func_Decl
: Node_Id
;
10750 Func_Id
: Entity_Id
;
10753 CRec_Typ
: Entity_Id
;
10754 -- The corresponding record type of Full_Typ
10756 Full_Typ
: Entity_Id
;
10757 -- The full view of Typ
10759 Priv_Typ
: Entity_Id
;
10760 -- The partial view of Typ
10762 UFull_Typ
: Entity_Id
;
10763 -- The underlying full view of Full_Typ
10766 -- The related type may be subject to pragma Ghost. Set the mode now to
10767 -- ensure that the predicate functions are properly marked as Ghost.
10769 Set_Ghost_Mode
(Typ
);
10772 Make_Defining_Identifier
(Loc
,
10773 Chars
=> New_External_Name
(Chars
(Typ
), "Predicate"));
10775 Mutate_Ekind
(Func_Id
, E_Function
);
10776 Set_Etype
(Func_Id
, Standard_Boolean
);
10777 Set_Is_Internal
(Func_Id
);
10778 Set_Is_Predicate_Function
(Func_Id
);
10779 Set_Predicate_Function
(Typ
, Func_Id
);
10781 -- The predicate function requires debug info when the predicates are
10782 -- subject to Source Coverage Obligations.
10784 if Opt
.Generate_SCO
then
10785 Set_Debug_Info_Needed
(Func_Id
);
10788 -- Obtain all views of the input type
10790 Get_Views
(Typ
, Priv_Typ
, Full_Typ
, UFull_Typ
, CRec_Typ
);
10792 -- Associate the predicate function and various flags with all views
10794 Propagate_Predicate_Attributes
(Priv_Typ
, From_Typ
=> Typ
);
10795 Propagate_Predicate_Attributes
(Full_Typ
, From_Typ
=> Typ
);
10796 Propagate_Predicate_Attributes
(UFull_Typ
, From_Typ
=> Typ
);
10797 Propagate_Predicate_Attributes
(CRec_Typ
, From_Typ
=> Typ
);
10800 Param_Specs
: constant List_Id
:= New_List
(
10801 Make_Parameter_Specification
(Loc
,
10802 Defining_Identifier
=> Make_Temporary
(Loc
, 'I'),
10803 Parameter_Type
=> New_Occurrence_Of
(Typ
, Loc
)));
10805 if Predicate_Function_Needs_Membership_Parameter
(Typ
) then
10806 -- Add Boolean-valued For_Membership_Test param
10807 Append
(Make_Parameter_Specification
(Loc
,
10808 Defining_Identifier
=> Make_Temporary
(Loc
, 'M'),
10810 New_Occurrence_Of
(Standard_Boolean
, Loc
)),
10815 Make_Function_Specification
(Loc
,
10816 Defining_Unit_Name
=> Func_Id
,
10817 Parameter_Specifications
=> Param_Specs
,
10818 Result_Definition
=>
10819 New_Occurrence_Of
(Standard_Boolean
, Loc
));
10822 Func_Decl
:= Make_Subprogram_Declaration
(Loc
, Specification
=> Spec
);
10824 Insert_After
(Parent
(Typ
), Func_Decl
);
10825 Analyze
(Func_Decl
);
10827 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
10830 end Build_Predicate_Function_Declaration
;
10832 -----------------------------------------
10833 -- Check_Aspect_At_End_Of_Declarations --
10834 -----------------------------------------
10836 procedure Check_Aspect_At_End_Of_Declarations
(ASN
: Node_Id
) is
10837 Ent
: constant Entity_Id
:= Entity
(ASN
);
10838 Ident
: constant Node_Id
:= Identifier
(ASN
);
10839 A_Id
: constant Aspect_Id
:= Get_Aspect_Id
(Chars
(Ident
));
10841 End_Decl_Expr
: constant Node_Id
:= Entity
(Ident
);
10842 -- Expression to be analyzed at end of declarations
10844 Freeze_Expr
: constant Node_Id
:= Expression
(ASN
);
10845 -- Expression from call to Check_Aspect_At_Freeze_Point.
10847 T
: constant Entity_Id
:=
10848 (if Present
(Freeze_Expr
) and A_Id
/= Aspect_Stable_Properties
10849 then Etype
(Original_Node
(Freeze_Expr
))
10851 -- Type required for preanalyze call. We use the original expression to
10852 -- get the proper type, to prevent cascaded errors when the expression
10853 -- is constant-folded. For Stable_Properties, the aspect value is
10854 -- not semantically an expression (although it is syntactically);
10855 -- in particular, it has no type.
10858 -- Set True if error
10860 -- On entry to this procedure, Entity (Ident) contains a copy of the
10861 -- original expression from the aspect, saved for this purpose, and
10862 -- but Expression (Ident) is a preanalyzed copy of the expression,
10863 -- preanalyzed just after the freeze point.
10865 procedure Check_Overloaded_Name
;
10866 -- For aspects whose expression is simply a name, this routine checks if
10867 -- the name is overloaded or not. If so, it verifies there is an
10868 -- interpretation that matches the entity obtained at the freeze point,
10869 -- otherwise the compiler complains.
10871 ---------------------------
10872 -- Check_Overloaded_Name --
10873 ---------------------------
10875 procedure Check_Overloaded_Name
is
10877 if not Is_Overloaded
(End_Decl_Expr
) then
10878 Err
:= not Is_Entity_Name
(End_Decl_Expr
)
10879 or else Entity
(End_Decl_Expr
) /= Entity
(Freeze_Expr
);
10885 Index
: Interp_Index
;
10889 Get_First_Interp
(End_Decl_Expr
, Index
, It
);
10890 while Present
(It
.Typ
) loop
10891 if It
.Nam
= Entity
(Freeze_Expr
) then
10896 Get_Next_Interp
(Index
, It
);
10900 end Check_Overloaded_Name
;
10902 -- Start of processing for Check_Aspect_At_End_Of_Declarations
10905 -- In an instance we do not perform the consistency check between freeze
10906 -- point and end of declarations, because it was done already in the
10907 -- analysis of the generic. Furthermore, the delayed analysis of an
10908 -- aspect of the instance may produce spurious errors when the generic
10909 -- is a child unit that references entities in the parent (which might
10910 -- not be in scope at the freeze point of the instance).
10912 if In_Instance
then
10915 -- The enclosing scope may have been rewritten during expansion (.e.g. a
10916 -- task body is rewritten as a procedure) after this conformance check
10917 -- has been performed, so do not perform it again (it may not easily be
10918 -- done if full visibility of local entities is not available).
10920 elsif not Comes_From_Source
(Current_Scope
) then
10923 -- Case of aspects Dimension, Dimension_System and Synchronization
10925 elsif A_Id
= Aspect_Synchronization
then
10928 -- Case of stream attributes and Put_Image, just have to compare
10929 -- entities. However, the expression is just a possibly-overloaded
10930 -- name, so we need to verify that one of these interpretations is
10931 -- the one available at at the freeze point.
10933 elsif A_Id
in Aspect_Input
10939 Analyze
(End_Decl_Expr
);
10940 Check_Overloaded_Name
;
10942 elsif A_Id
in Aspect_Variable_Indexing
10943 | Aspect_Constant_Indexing
10944 | Aspect_Default_Iterator
10945 | Aspect_Iterator_Element
10946 | Aspect_Integer_Literal
10947 | Aspect_Real_Literal
10948 | Aspect_String_Literal
10950 -- Make type unfrozen before analysis, to prevent spurious errors
10951 -- about late attributes.
10953 Set_Is_Frozen
(Ent
, False);
10954 Analyze
(End_Decl_Expr
);
10955 Set_Is_Frozen
(Ent
, True);
10957 -- If the end of declarations comes before any other freeze point,
10958 -- the Freeze_Expr is not analyzed: no check needed.
10960 if Analyzed
(Freeze_Expr
) and then not In_Instance
then
10961 Check_Overloaded_Name
;
10969 -- In a generic context freeze nodes are not always generated, so
10970 -- analyze the expression now. If the aspect is for a type, we must
10971 -- also make its potential components accessible.
10973 if not Analyzed
(Freeze_Expr
) and then Inside_A_Generic
then
10974 if A_Id
in Aspect_Dynamic_Predicate
10975 | Aspect_Ghost_Predicate
10977 | Aspect_Static_Predicate
10980 Preanalyze_Spec_Expression
(Freeze_Expr
, Standard_Boolean
);
10983 elsif A_Id
= Aspect_Priority
then
10985 Preanalyze_Spec_Expression
(Freeze_Expr
, Any_Integer
);
10989 Preanalyze
(Freeze_Expr
);
10993 -- Indicate that the expression comes from an aspect specification,
10994 -- which is used in subsequent analysis even if expansion is off.
10996 if Present
(End_Decl_Expr
) then
10997 Set_Parent
(End_Decl_Expr
, ASN
);
11000 -- In a generic context the original aspect expressions have not
11001 -- been preanalyzed, so do it now. There are no conformance checks
11002 -- to perform in this case. As before, we have to make components
11003 -- visible for aspects that may reference them.
11005 if Present
(Freeze_Expr
) and then No
(T
) then
11006 if A_Id
in Aspect_Dynamic_Predicate
11007 | Aspect_Ghost_Predicate
11010 | Aspect_Static_Predicate
11013 Check_Aspect_At_Freeze_Point
(ASN
);
11017 Check_Aspect_At_Freeze_Point
(ASN
);
11021 -- The default values attributes may be defined in the private part,
11022 -- and the analysis of the expression may take place when only the
11023 -- partial view is visible. The expression must be scalar, so use
11024 -- the full view to resolve.
11026 elsif A_Id
in Aspect_Default_Component_Value | Aspect_Default_Value
11027 and then Is_Private_Type
(T
)
11029 Preanalyze_Spec_Expression
(End_Decl_Expr
, Full_View
(T
));
11031 -- The following aspect expressions may contain references to
11032 -- components and discriminants of the type.
11034 elsif A_Id
in Aspect_CPU
11035 | Aspect_Dynamic_Predicate
11036 | Aspect_Ghost_Predicate
11039 | Aspect_Static_Predicate
11042 Preanalyze_Spec_Expression
(End_Decl_Expr
, T
);
11045 elsif A_Id
= Aspect_Predicate_Failure
then
11046 Preanalyze_Spec_Expression
(End_Decl_Expr
, Standard_String
);
11047 elsif Present
(End_Decl_Expr
) then
11048 Preanalyze_Spec_Expression
(End_Decl_Expr
, T
);
11052 not Fully_Conformant_Expressions
11053 (End_Decl_Expr
, Freeze_Expr
, Report
=> True);
11056 -- Output error message if error. Force error on aspect specification
11057 -- even if there is an error on the expression itself.
11061 ("!visibility of aspect for& changes after freeze point",
11064 ("info: & is frozen here, (RM 13.1.1 (13/3))??",
11065 Freeze_Node
(Ent
), Ent
);
11067 end Check_Aspect_At_End_Of_Declarations
;
11069 ----------------------------------
11070 -- Check_Aspect_At_Freeze_Point --
11071 ----------------------------------
11073 procedure Check_Aspect_At_Freeze_Point
(ASN
: Node_Id
) is
11074 Ident
: constant Node_Id
:= Identifier
(ASN
);
11075 -- Identifier (use Entity field to save expression)
11077 Expr
: constant Node_Id
:= Expression
(ASN
);
11078 -- For cases where using Entity (Identifier) doesn't work
11080 A_Id
: constant Aspect_Id
:= Get_Aspect_Id
(Chars
(Ident
));
11082 T
: Entity_Id
:= Empty
;
11083 -- Type required for preanalyze call
11086 -- On entry to this procedure, Entity (Ident) contains a copy of the
11087 -- original expression from the aspect, saved for this purpose.
11089 -- On exit from this procedure Entity (Ident) is unchanged, still
11090 -- containing that copy, but Expression (Ident) is a preanalyzed copy
11091 -- of the expression, preanalyzed just after the freeze point.
11093 -- Make a copy of the expression to be preanalyzed
11095 Set_Expression
(ASN
, New_Copy_Tree
(Entity
(Ident
)));
11097 -- Find type for preanalyze call
11101 -- No_Aspect should be impossible
11104 raise Program_Error
;
11106 -- Aspects taking an optional boolean argument
11108 when Boolean_Aspects
11109 | Library_Unit_Aspects
11111 T
:= Standard_Boolean
;
11113 -- Aspects corresponding to attribute definition clauses
11115 when Aspect_Address
=>
11116 T
:= RTE
(RE_Address
);
11118 when Aspect_Attach_Handler
=>
11119 T
:= RTE
(RE_Interrupt_ID
);
11121 when Aspect_Bit_Order
11122 | Aspect_Scalar_Storage_Order
11124 T
:= RTE
(RE_Bit_Order
);
11126 when Aspect_Convention
=>
11130 T
:= RTE
(RE_CPU_Range
);
11132 -- Default_Component_Value is resolved with the component type
11134 when Aspect_Default_Component_Value
=>
11135 T
:= Component_Type
(Entity
(ASN
));
11137 when Aspect_Default_Storage_Pool
=>
11138 T
:= Class_Wide_Type
(RTE
(RE_Root_Storage_Pool
));
11140 -- Default_Value is resolved with the type entity in question
11142 when Aspect_Default_Value
=>
11145 when Aspect_Dispatching_Domain
=>
11146 T
:= RTE
(RE_Dispatching_Domain
);
11148 when Aspect_External_Tag
=>
11149 T
:= Standard_String
;
11151 when Aspect_External_Name
=>
11152 T
:= Standard_String
;
11154 when Aspect_Link_Name
=>
11155 T
:= Standard_String
;
11157 when Aspect_Interrupt_Priority
11160 T
:= Standard_Integer
;
11162 when Aspect_Relative_Deadline
=>
11163 T
:= RTE
(RE_Time_Span
);
11165 when Aspect_Secondary_Stack_Size
=>
11166 T
:= Standard_Integer
;
11168 when Aspect_Small
=>
11170 -- Note that the expression can be of any real type (not just a
11171 -- real universal literal) as long as it is a static constant.
11175 -- For a simple storage pool, we have to retrieve the type of the
11176 -- pool object associated with the aspect's corresponding attribute
11177 -- definition clause.
11179 when Aspect_Simple_Storage_Pool
=>
11180 T
:= Etype
(Expression
(Aspect_Rep_Item
(ASN
)));
11182 when Aspect_Storage_Pool
=>
11183 T
:= Class_Wide_Type
(RTE
(RE_Root_Storage_Pool
));
11185 when Aspect_Alignment
11186 | Aspect_Component_Size
11187 | Aspect_Machine_Radix
11188 | Aspect_Object_Size
11190 | Aspect_Storage_Size
11191 | Aspect_Stream_Size
11192 | Aspect_Value_Size
11196 when Aspect_Linker_Section
=>
11197 T
:= Standard_String
;
11199 when Aspect_Synchronization
=>
11202 -- Special case, the expression of these aspects is just an entity
11203 -- that does not need any resolution, so just analyze.
11212 Analyze
(Expression
(ASN
));
11215 -- Same for Iterator aspects, where the expression is a function
11216 -- name. Legality rules are checked separately.
11218 when Aspect_Constant_Indexing
11219 | Aspect_Default_Iterator
11220 | Aspect_Iterator_Element
11221 | Aspect_Variable_Indexing
11223 Analyze
(Expression
(ASN
));
11226 -- Same for Literal aspects, where the expression is a function
11227 -- name. Legality rules are checked separately. Use Expr to avoid
11228 -- losing track of the previous resolution of Expression.
11230 when Aspect_Integer_Literal
11231 | Aspect_Real_Literal
11232 | Aspect_String_Literal
11234 Set_Entity
(Expression
(ASN
), Entity
(Expr
));
11235 Set_Etype
(Expression
(ASN
), Etype
(Expr
));
11236 Set_Is_Overloaded
(Expression
(ASN
), False);
11237 Analyze
(Expression
(ASN
));
11240 -- Ditto for Iterable, legality checks in Validate_Iterable_Aspect.
11242 when Aspect_Iterable
=>
11246 Cursor
: constant Entity_Id
:= Get_Cursor_Type
(ASN
, T
);
11251 if Cursor
= Any_Type
then
11255 Assoc
:= First
(Component_Associations
(Expression
(ASN
)));
11256 while Present
(Assoc
) loop
11257 Expr
:= Expression
(Assoc
);
11260 if not Error_Posted
(Expr
) then
11261 Resolve_Iterable_Operation
11262 (Expr
, Cursor
, T
, Chars
(First
(Choices
(Assoc
))));
11271 when Aspect_Aggregate
=>
11272 if Is_Array_Type
(Entity
(ASN
)) then
11274 ("aspect& can only be applied to non-array type",
11277 Resolve_Aspect_Aggregate
(Entity
(ASN
), Expression
(ASN
));
11280 when Aspect_Stable_Properties
=>
11281 Resolve_Aspect_Stable_Properties
11282 (Entity
(ASN
), Expression
(ASN
),
11283 Class_Present
=> Class_Present
(ASN
));
11286 -- Invariant/Predicate take boolean expressions
11288 when Aspect_Dynamic_Predicate
11290 | Aspect_Ghost_Predicate
11292 | Aspect_Static_Predicate
11293 | Aspect_Type_Invariant
11295 T
:= Standard_Boolean
;
11297 when Aspect_Predicate_Failure
=>
11298 T
:= Standard_String
;
11300 -- As for some other aspects above, the expression of this aspect is
11301 -- just an entity that does not need any resolution, so just analyze.
11303 when Aspect_Designated_Storage_Model
=>
11304 Analyze
(Expression
(ASN
));
11307 when Aspect_Storage_Model_Type
=>
11309 -- The aggregate argument of Storage_Model_Type is optional, and
11310 -- when not present the aspect defaults to the native storage
11311 -- model (where the address type is System.Address, and other
11312 -- arguments default to corresponding native storage operations).
11314 if No
(Expression
(ASN
)) then
11323 Addr_Type
: Entity_Id
:= Empty
;
11326 Assoc
:= First
(Component_Associations
(Expression
(ASN
)));
11327 while Present
(Assoc
) loop
11328 Expr
:= Expression
(Assoc
);
11331 if not Error_Posted
(Expr
) then
11332 Resolve_Storage_Model_Type_Argument
11333 (Expr
, T
, Addr_Type
, Chars
(First
(Choices
(Assoc
))));
11342 -- Here is the list of aspects that don't require delay analysis
11344 when Aspect_Abstract_State
11345 | Aspect_Always_Terminates
11347 | Aspect_Async_Readers
11348 | Aspect_Async_Writers
11349 | Aspect_Constant_After_Elaboration
11350 | Aspect_Contract_Cases
11351 | Aspect_Default_Initial_Condition
11354 | Aspect_Dimension_System
11355 | Aspect_Exceptional_Cases
11356 | Aspect_Effective_Reads
11357 | Aspect_Effective_Writes
11358 | Aspect_Extensions_Visible
11361 | Aspect_GNAT_Annotate
11362 | Aspect_Implicit_Dereference
11363 | Aspect_Initial_Condition
11364 | Aspect_Initializes
11365 | Aspect_Max_Entry_Queue_Depth
11366 | Aspect_Max_Entry_Queue_Length
11367 | Aspect_Max_Queue_Length
11368 | Aspect_No_Caching
11369 | Aspect_No_Controlled_Parts
11370 | Aspect_No_Task_Parts
11371 | Aspect_Obsolescent
11374 | Aspect_Postcondition
11376 | Aspect_Precondition
11377 | Aspect_Refined_Depends
11378 | Aspect_Refined_Global
11379 | Aspect_Refined_Post
11380 | Aspect_Refined_State
11381 | Aspect_Relaxed_Initialization
11382 | Aspect_SPARK_Mode
11383 | Aspect_Subprogram_Variant
11386 | Aspect_Unimplemented
11387 | Aspect_Unsuppress
11388 | Aspect_Volatile_Function
11390 raise Program_Error
;
11394 -- Do the preanalyze call
11396 if Present
(Expression
(ASN
)) then
11397 Preanalyze_Spec_Expression
(Expression
(ASN
), T
);
11399 end Check_Aspect_At_Freeze_Point
;
11401 -----------------------------------
11402 -- Check_Constant_Address_Clause --
11403 -----------------------------------
11405 procedure Check_Constant_Address_Clause
11409 procedure Check_At_Constant_Address
(Nod
: Node_Id
);
11410 -- Checks that the given node N represents a name whose 'Address is
11411 -- constant (in the same sense as OK_Constant_Address_Clause, i.e. the
11412 -- address value is the same at the point of declaration of U_Ent and at
11413 -- the time of elaboration of the address clause.
11415 procedure Check_Expr_Constants
(Nod
: Node_Id
);
11416 -- Checks that Nod meets the requirements for a constant address clause
11417 -- in the sense of the enclosing procedure.
11419 procedure Check_List_Constants
(Lst
: List_Id
);
11420 -- Check that all elements of list Lst meet the requirements for a
11421 -- constant address clause in the sense of the enclosing procedure.
11423 -------------------------------
11424 -- Check_At_Constant_Address --
11425 -------------------------------
11427 procedure Check_At_Constant_Address
(Nod
: Node_Id
) is
11429 if Is_Entity_Name
(Nod
) then
11430 if Present
(Address_Clause
(Entity
((Nod
)))) then
11432 ("invalid address clause for initialized object &!",
11435 ("address for& cannot depend on another address clause! "
11436 & "(RM 13.1(22))!", Nod
, U_Ent
);
11438 elsif In_Same_Source_Unit
(Entity
(Nod
), U_Ent
)
11439 and then Sloc
(U_Ent
) < Sloc
(Entity
(Nod
))
11442 ("invalid address clause for initialized object &!",
11444 Error_Msg_Node_2
:= U_Ent
;
11446 ("\& must be defined before & (RM 13.1(22))!",
11447 Nod
, Entity
(Nod
));
11450 elsif Nkind
(Nod
) = N_Selected_Component
then
11452 T
: constant Entity_Id
:= Etype
(Prefix
(Nod
));
11455 if (Is_Record_Type
(T
)
11456 and then Has_Discriminants
(T
))
11458 (Is_Access_Type
(T
)
11459 and then Is_Record_Type
(Designated_Type
(T
))
11460 and then Has_Discriminants
(Designated_Type
(T
)))
11463 ("invalid address clause for initialized object &!",
11466 ("\address cannot depend on component of discriminated "
11467 & "record (RM 13.1(22))!", Nod
);
11469 Check_At_Constant_Address
(Prefix
(Nod
));
11473 elsif Nkind
(Nod
) = N_Indexed_Component
then
11474 Check_At_Constant_Address
(Prefix
(Nod
));
11475 Check_List_Constants
(Expressions
(Nod
));
11478 Check_Expr_Constants
(Nod
);
11480 end Check_At_Constant_Address
;
11482 --------------------------
11483 -- Check_Expr_Constants --
11484 --------------------------
11486 procedure Check_Expr_Constants
(Nod
: Node_Id
) is
11487 Loc_U_Ent
: constant Source_Ptr
:= Sloc
(U_Ent
);
11488 Ent
: Entity_Id
:= Empty
;
11491 if Nkind
(Nod
) in N_Has_Etype
11492 and then Etype
(Nod
) = Any_Type
11497 case Nkind
(Nod
) is
11503 when N_Expanded_Name
11506 Ent
:= Entity
(Nod
);
11508 -- We need to look at the original node if it is different
11509 -- from the node, since we may have rewritten things and
11510 -- substituted an identifier representing the rewrite.
11512 if Is_Rewrite_Substitution
(Nod
) then
11513 Check_Expr_Constants
(Original_Node
(Nod
));
11515 -- If the node is an object declaration without initial
11516 -- value, some code has been expanded, and the expression
11517 -- is not constant, even if the constituents might be
11518 -- acceptable, as in A'Address + offset.
11520 if Ekind
(Ent
) = E_Variable
11522 Nkind
(Declaration_Node
(Ent
)) = N_Object_Declaration
11524 No
(Expression
(Declaration_Node
(Ent
)))
11527 ("invalid address clause for initialized object &!",
11530 -- If entity is constant, it may be the result of expanding
11531 -- a check. We must verify that its declaration appears
11532 -- before the object in question, else we also reject the
11535 elsif Ekind
(Ent
) = E_Constant
11536 and then In_Same_Source_Unit
(Ent
, U_Ent
)
11537 and then Sloc
(Ent
) > Loc_U_Ent
11540 ("invalid address clause for initialized object &!",
11547 -- Otherwise look at the identifier and see if it is OK
11549 if Is_Named_Number
(Ent
) or else Is_Type
(Ent
) then
11552 elsif Ekind
(Ent
) in E_Constant | E_In_Parameter
then
11554 -- This is the case where we must have Ent defined before
11555 -- U_Ent. Clearly if they are in different units this
11556 -- requirement is met since the unit containing Ent is
11557 -- already processed.
11559 if not In_Same_Source_Unit
(Ent
, U_Ent
) then
11562 -- Otherwise location of Ent must be before the location
11563 -- of U_Ent, that's what prior defined means.
11565 elsif Sloc
(Ent
) < Loc_U_Ent
then
11570 ("invalid address clause for initialized object &!",
11572 Error_Msg_Node_2
:= U_Ent
;
11574 ("\& must be defined before & (RM 13.1(22))!",
11578 elsif Nkind
(Original_Node
(Nod
)) = N_Function_Call
then
11579 Check_Expr_Constants
(Original_Node
(Nod
));
11583 ("invalid address clause for initialized object &!",
11586 if Comes_From_Source
(Ent
) then
11588 ("\reference to variable& not allowed"
11589 & " (RM 13.1(22))!", Nod
, Ent
);
11592 ("non-static expression not allowed"
11593 & " (RM 13.1(22))!", Nod
);
11597 when N_Integer_Literal
=>
11599 -- If this is a rewritten unchecked conversion, in a system
11600 -- where Address is an integer type, always use the base type
11601 -- for a literal value. This is user-friendly and prevents
11602 -- order-of-elaboration issues with instances of unchecked
11605 if Nkind
(Original_Node
(Nod
)) = N_Function_Call
then
11606 Set_Etype
(Nod
, Base_Type
(Etype
(Nod
)));
11609 when N_Character_Literal
11616 Check_Expr_Constants
(Low_Bound
(Nod
));
11617 Check_Expr_Constants
(High_Bound
(Nod
));
11619 when N_Explicit_Dereference
=>
11620 Check_Expr_Constants
(Prefix
(Nod
));
11622 when N_Indexed_Component
=>
11623 Check_Expr_Constants
(Prefix
(Nod
));
11624 Check_List_Constants
(Expressions
(Nod
));
11627 Check_Expr_Constants
(Prefix
(Nod
));
11628 Check_Expr_Constants
(Discrete_Range
(Nod
));
11630 when N_Selected_Component
=>
11631 Check_Expr_Constants
(Prefix
(Nod
));
11633 when N_Attribute_Reference
=>
11634 if Attribute_Name
(Nod
) in Name_Address
11636 | Name_Unchecked_Access
11637 | Name_Unrestricted_Access
11639 Check_At_Constant_Address
(Prefix
(Nod
));
11641 -- Normally, System'To_Address will have been transformed into
11642 -- an Unchecked_Conversion, but in -gnatc mode, it will not,
11643 -- and we don't want to give an error, because the whole point
11644 -- of 'To_Address is that it is static.
11646 elsif Attribute_Name
(Nod
) = Name_To_Address
then
11647 pragma Assert
(Operating_Mode
= Check_Semantics
);
11651 Check_Expr_Constants
(Prefix
(Nod
));
11652 Check_List_Constants
(Expressions
(Nod
));
11655 when N_Aggregate
=>
11656 Check_List_Constants
(Component_Associations
(Nod
));
11657 Check_List_Constants
(Expressions
(Nod
));
11659 when N_Component_Association
=>
11660 Check_Expr_Constants
(Expression
(Nod
));
11662 when N_Extension_Aggregate
=>
11663 Check_Expr_Constants
(Ancestor_Part
(Nod
));
11664 Check_List_Constants
(Component_Associations
(Nod
));
11665 Check_List_Constants
(Expressions
(Nod
));
11671 | N_Membership_Test
11674 Check_Expr_Constants
(Left_Opnd
(Nod
));
11675 Check_Expr_Constants
(Right_Opnd
(Nod
));
11678 Check_Expr_Constants
(Right_Opnd
(Nod
));
11681 | N_Qualified_Expression
11682 | N_Type_Conversion
11683 | N_Unchecked_Type_Conversion
11685 Check_Expr_Constants
(Expression
(Nod
));
11687 when N_Function_Call
=>
11688 if not Is_Pure
(Entity
(Name
(Nod
))) then
11690 ("invalid address clause for initialized object &!",
11694 ("\function & is not pure (RM 13.1(22))!",
11695 Nod
, Entity
(Name
(Nod
)));
11698 Check_List_Constants
(Parameter_Associations
(Nod
));
11701 when N_Parameter_Association
=>
11702 Check_Expr_Constants
(Explicit_Actual_Parameter
(Nod
));
11706 ("invalid address clause for initialized object &!",
11709 ("\must be constant defined before& (RM 13.1(22))!",
11712 end Check_Expr_Constants
;
11714 --------------------------
11715 -- Check_List_Constants --
11716 --------------------------
11718 procedure Check_List_Constants
(Lst
: List_Id
) is
11722 Nod1
:= First
(Lst
);
11723 while Present
(Nod1
) loop
11724 Check_Expr_Constants
(Nod1
);
11727 end Check_List_Constants
;
11729 -- Start of processing for Check_Constant_Address_Clause
11732 -- If rep_clauses are to be ignored, no need for legality checks. In
11733 -- particular, no need to pester user about rep clauses that violate the
11734 -- rule on constant addresses, given that these clauses will be removed
11735 -- by Freeze before they reach the back end. Similarly in CodePeer mode,
11736 -- we want to relax these checks.
11738 if not Ignore_Rep_Clauses
and not CodePeer_Mode
then
11739 Check_Expr_Constants
(Expr
);
11741 end Check_Constant_Address_Clause
;
11743 ---------------------------
11744 -- Check_Pool_Size_Clash --
11745 ---------------------------
11747 procedure Check_Pool_Size_Clash
(Ent
: Entity_Id
; SP
, SS
: Node_Id
) is
11751 -- We need to find out which one came first. Note that in the case of
11752 -- aspects mixed with pragmas there are cases where the processing order
11753 -- is reversed, which is why we do the check here.
11755 if Sloc
(SP
) < Sloc
(SS
) then
11756 Error_Msg_Sloc
:= Sloc
(SP
);
11758 Error_Msg_NE
("Storage_Pool previously given for&#", Post
, Ent
);
11761 Error_Msg_Sloc
:= Sloc
(SS
);
11763 Error_Msg_NE
("Storage_Size previously given for&#", Post
, Ent
);
11767 ("\cannot have Storage_Size and Storage_Pool (RM 13.11(3))", Post
);
11768 end Check_Pool_Size_Clash
;
11770 ----------------------------------------
11771 -- Check_Record_Representation_Clause --
11772 ----------------------------------------
11774 procedure Check_Record_Representation_Clause
(N
: Node_Id
) is
11775 Loc
: constant Source_Ptr
:= Sloc
(N
);
11776 Ident
: constant Node_Id
:= Identifier
(N
);
11777 Rectype
: Entity_Id
;
11780 Fbit
: Uint
:= No_Uint
;
11781 Lbit
: Uint
:= No_Uint
;
11782 Hbit
: Uint
:= Uint_0
;
11786 Max_Bit_So_Far
: Uint
;
11787 -- Records the maximum bit position so far. If all field positions
11788 -- are monotonically increasing, then we can skip the circuit for
11789 -- checking for overlap, since no overlap is possible.
11791 Tagged_Parent
: Entity_Id
:= Empty
;
11792 -- This is set in the case of an extension for which we have either a
11793 -- size clause or Is_Fully_Repped_Tagged_Type True (indicating that all
11794 -- components are positioned by record representation clauses) on the
11795 -- parent type. In this case we check for overlap between components of
11796 -- this tagged type and the parent component. Tagged_Parent will point
11797 -- to this parent type. For all other cases, Tagged_Parent is Empty.
11799 Parent_Last_Bit
: Uint
:= No_Uint
; -- init to avoid warning
11800 -- Relevant only if Tagged_Parent is set, Parent_Last_Bit indicates the
11801 -- last bit position for any field in the parent type. We only need to
11802 -- check overlap for fields starting below this point.
11804 Overlap_Check_Required
: Boolean;
11805 -- Used to keep track of whether or not an overlap check is required
11807 Overlap_Detected
: Boolean := False;
11808 -- Set True if an overlap is detected
11810 Ccount
: Natural := 0;
11811 -- Number of component clauses in record rep clause
11813 procedure Check_Component_Overlap
(C1_Ent
, C2_Ent
: Entity_Id
);
11814 -- Given two entities for record components or discriminants, checks
11815 -- if they have overlapping component clauses and issues errors if so.
11817 procedure Find_Component
;
11818 -- Finds component entity corresponding to current component clause (in
11819 -- CC), and sets Comp to the entity, and Fbit/Lbit to the zero origin
11820 -- start/stop bits for the field. If there is no matching component or
11821 -- if the matching component does not have a component clause, then
11822 -- that's an error and Comp is set to Empty, but no error message is
11823 -- issued, since the message was already given. Comp is also set to
11824 -- Empty if the current "component clause" is in fact a pragma.
11826 procedure Record_Hole_Check
11827 (Rectype
: Entity_Id
; After_Last
: out Uint
; Warn
: Boolean);
11828 -- Checks for gaps in the given Rectype. Compute After_Last, the bit
11829 -- number after the last component. Warn is True on the initial call,
11830 -- and warnings are given for gaps. For a type extension, this is called
11831 -- recursively to compute After_Last for the parent type; in this case
11832 -- Warn is False and the warnings are suppressed.
11834 procedure Component_Order_Check
(Rectype
: Entity_Id
);
11835 -- Check that the order of component clauses agrees with the order of
11836 -- component declarations, and that the component clauses are given in
11837 -- increasing order of bit offset.
11839 -----------------------------
11840 -- Check_Component_Overlap --
11841 -----------------------------
11843 procedure Check_Component_Overlap
(C1_Ent
, C2_Ent
: Entity_Id
) is
11844 CC1
: constant Node_Id
:= Component_Clause
(C1_Ent
);
11845 CC2
: constant Node_Id
:= Component_Clause
(C2_Ent
);
11848 if Present
(CC1
) and then Present
(CC2
) then
11850 -- Exclude odd case where we have two tag components in the same
11851 -- record, both at location zero. This seems a bit strange, but
11852 -- it seems to happen in some circumstances, perhaps on an error.
11854 if Chars
(C1_Ent
) = Name_uTag
then
11858 -- Here we check if the two fields overlap
11861 S1
: constant Uint
:= Component_Bit_Offset
(C1_Ent
);
11862 S2
: constant Uint
:= Component_Bit_Offset
(C2_Ent
);
11863 E1
: constant Uint
:= S1
+ Esize
(C1_Ent
);
11864 E2
: constant Uint
:= S2
+ Esize
(C2_Ent
);
11867 if E2
<= S1
or else E1
<= S2
then
11870 Error_Msg_Node_2
:= Component_Name
(CC2
);
11871 Error_Msg_Sloc
:= Sloc
(Error_Msg_Node_2
);
11872 Error_Msg_Node_1
:= Component_Name
(CC1
);
11874 ("component& overlaps & #", Component_Name
(CC1
));
11875 Overlap_Detected
:= True;
11879 end Check_Component_Overlap
;
11881 ---------------------------
11882 -- Component_Order_Check --
11883 ---------------------------
11885 procedure Component_Order_Check
(Rectype
: Entity_Id
) is
11886 Comp
: Entity_Id
:= First_Component
(Rectype
);
11887 Clause
: Node_Id
:= First
(Component_Clauses
(N
));
11888 Prev_Bit_Offset
: Uint
:= Uint_0
;
11889 OOO
: constant String :=
11890 "?_r?component clause out of order with respect to declaration";
11893 -- Step Comp through components and Clause through component clauses,
11894 -- skipping pragmas. We ignore discriminants and variant parts,
11895 -- because we get most of the benefit from the plain vanilla
11896 -- component cases, without the extra complexity. If we find a Comp
11897 -- and Clause that don't match, give a warning on both and quit. If
11898 -- we find two subsequent clauses out of order by bit layout, give
11899 -- warning and quit. On each iteration, Prev_Bit_Offset is the one
11900 -- from the previous iteration (or 0 to start).
11902 while Present
(Comp
) and then Present
(Clause
) loop
11903 if Nkind
(Clause
) = N_Component_Clause
11904 and then Ekind
(Entity
(Component_Name
(Clause
))) = E_Component
11906 if Entity
(Component_Name
(Clause
)) /= Comp
then
11907 Error_Msg_N
(OOO
, Comp
);
11908 Error_Msg_N
(OOO
, Clause
);
11912 if not Reverse_Bit_Order
(Rectype
)
11913 and then not Reverse_Storage_Order
(Rectype
)
11914 and then Component_Bit_Offset
(Comp
) < Prev_Bit_Offset
11916 Error_Msg_N
("?_r?memory layout out of order", Clause
);
11920 Prev_Bit_Offset
:= Component_Bit_Offset
(Comp
);
11921 Next_Component
(Comp
);
11926 end Component_Order_Check
;
11928 --------------------
11929 -- Find_Component --
11930 --------------------
11932 procedure Find_Component
is
11934 procedure Search_Component
(R
: Entity_Id
);
11935 -- Search components of R for a match. If found, Comp is set
11937 ----------------------
11938 -- Search_Component --
11939 ----------------------
11941 procedure Search_Component
(R
: Entity_Id
) is
11943 Comp
:= First_Component_Or_Discriminant
(R
);
11944 while Present
(Comp
) loop
11946 -- Ignore error of attribute name for component name (we
11947 -- already gave an error message for this, so no need to
11950 if Nkind
(Component_Name
(CC
)) = N_Attribute_Reference
then
11953 exit when Chars
(Comp
) = Chars
(Component_Name
(CC
));
11956 Next_Component_Or_Discriminant
(Comp
);
11958 end Search_Component
;
11960 -- Start of processing for Find_Component
11963 -- Return with Comp set to Empty if we have a pragma
11965 if Nkind
(CC
) = N_Pragma
then
11970 -- Search current record for matching component
11972 Search_Component
(Rectype
);
11974 -- If not found, maybe component of base type discriminant that is
11975 -- absent from statically constrained first subtype.
11978 Search_Component
(Base_Type
(Rectype
));
11981 -- If no component, or the component does not reference the component
11982 -- clause in question, then there was some previous error for which
11983 -- we already gave a message, so just return with Comp Empty.
11985 if No
(Comp
) or else Component_Clause
(Comp
) /= CC
then
11986 Check_Error_Detected
;
11989 -- Normal case where we have a component clause
11992 Fbit
:= Component_Bit_Offset
(Comp
);
11993 Lbit
:= Fbit
+ Esize
(Comp
) - 1;
11995 end Find_Component
;
11997 -----------------------
11998 -- Record_Hole_Check --
11999 -----------------------
12001 procedure Record_Hole_Check
12002 (Rectype
: Entity_Id
; After_Last
: out Uint
; Warn
: Boolean)
12004 Decl
: constant Node_Id
:= Declaration_Node
(Base_Type
(Rectype
));
12005 -- Full declaration of record type
12007 procedure Check_Component_List
12012 -- Check component list CL for holes. DS is a list of discriminant
12013 -- specifications to be included in the consideration of components.
12014 -- Sbit is the starting bit, which is zero if there are no preceding
12015 -- components (before a variant part, or a parent type, or a tag
12016 -- field). If there are preceding components, Sbit is the bit just
12017 -- after the last such component. Abit is set to the bit just after
12018 -- the last component of DS and CL.
12020 --------------------------
12021 -- Check_Component_List --
12022 --------------------------
12024 procedure Check_Component_List
12030 Compl
: constant Natural :=
12031 Natural (List_Length
(Component_Items
(CL
)) + List_Length
(DS
));
12033 Comps
: array (Natural range 0 .. Compl
) of Entity_Id
;
12034 -- Gather components (zero entry is for sort routine)
12036 Ncomps
: Natural := 0;
12037 -- Number of entries stored in Comps (starting at Comps (1))
12040 -- One component item or discriminant specification
12043 -- Starting bit for next component
12046 -- Component entity
12051 function Lt
(Op1
, Op2
: Natural) return Boolean;
12052 -- Compare routine for Sort
12054 procedure Move
(From
: Natural; To
: Natural);
12055 -- Move routine for Sort
12057 package Sorting
is new GNAT
.Heap_Sort_G
(Move
, Lt
);
12063 function Lt
(Op1
, Op2
: Natural) return Boolean is
12064 K1
: constant Boolean :=
12065 Known_Component_Bit_Offset
(Comps
(Op1
));
12066 K2
: constant Boolean :=
12067 Known_Component_Bit_Offset
(Comps
(Op2
));
12068 -- Record representation clauses can be incomplete, so the
12069 -- Component_Bit_Offsets can be unknown.
12073 return Component_Bit_Offset
(Comps
(Op1
))
12074 < Component_Bit_Offset
(Comps
(Op2
));
12087 procedure Move
(From
: Natural; To
: Natural) is
12089 Comps
(To
) := Comps
(From
);
12092 -- Start of processing for Check_Component_List
12095 -- Gather discriminants into Comp
12097 Citem
:= First
(DS
);
12098 while Present
(Citem
) loop
12099 if Nkind
(Citem
) = N_Discriminant_Specification
then
12101 Ent
: constant Entity_Id
:=
12102 Defining_Identifier
(Citem
);
12104 if Ekind
(Ent
) = E_Discriminant
then
12105 Ncomps
:= Ncomps
+ 1;
12106 Comps
(Ncomps
) := Ent
;
12114 -- Gather component entities into Comp
12116 Citem
:= First
(Component_Items
(CL
));
12117 while Present
(Citem
) loop
12118 if Nkind
(Citem
) = N_Component_Declaration
then
12119 Ncomps
:= Ncomps
+ 1;
12120 Comps
(Ncomps
) := Defining_Identifier
(Citem
);
12126 -- Now sort the component entities based on the first bit.
12127 -- Note we already know there are no overlapping components.
12129 Sorting
.Sort
(Ncomps
);
12131 -- Loop through entries checking for holes
12134 for J
in 1 .. Ncomps
loop
12136 pragma Annotate
(CodePeer
, Modified
, CEnt
);
12139 CBO
: constant Uint
:= Component_Bit_Offset
(CEnt
);
12142 -- Skip components with unknown offsets
12144 if Present
(CBO
) and then CBO
>= 0 then
12145 Error_Msg_Uint_1
:= CBO
- Nbit
;
12147 if Warn
and then Error_Msg_Uint_1
> 0 then
12149 ("?.h?^-bit gap before component&",
12150 Component_Name
(Component_Clause
(CEnt
)),
12154 Nbit
:= CBO
+ Esize
(CEnt
);
12159 -- Set Abit to just after the last nonvariant component
12163 -- Process variant parts recursively if present. Set Abit to the
12164 -- maximum for all variant parts.
12166 if Present
(Variant_Part
(CL
)) then
12168 Var_Start
: constant Uint
:= Nbit
;
12170 Variant
:= First
(Variants
(Variant_Part
(CL
)));
12171 while Present
(Variant
) loop
12172 Check_Component_List
12173 (No_List
, Component_List
(Variant
), Var_Start
, Nbit
);
12175 if Nbit
> Abit
then
12181 end Check_Component_List
;
12186 -- Starting bit for call to Check_Component_List. Zero for an
12187 -- untagged type. The size of the Tag for a nonderived tagged
12188 -- type. Parent size for a type extension.
12190 Record_Definition
: Node_Id
;
12191 -- Record_Definition containing Component_List to pass to
12192 -- Check_Component_List.
12194 -- Start of processing for Record_Hole_Check
12197 if Is_Tagged_Type
(Rectype
) then
12198 Sbit
:= UI_From_Int
(System_Address_Size
);
12203 After_Last
:= Uint_0
;
12205 if Nkind
(Decl
) = N_Full_Type_Declaration
then
12206 Record_Definition
:= Type_Definition
(Decl
);
12208 -- If we have a record extension, set Sbit to point after the last
12209 -- component of the parent type, by calling Record_Hole_Check
12212 if Nkind
(Record_Definition
) = N_Derived_Type_Definition
then
12213 Record_Definition
:= Record_Extension_Part
(Record_Definition
);
12214 Record_Hole_Check
(Underlying_Type
(Parent_Subtype
(Rectype
)),
12215 After_Last
=> Sbit
, Warn
=> False);
12218 if Nkind
(Record_Definition
) = N_Record_Definition
then
12219 Check_Component_List
12220 (Discriminant_Specifications
(Decl
),
12221 Component_List
(Record_Definition
),
12225 end Record_Hole_Check
;
12227 -- Start of processing for Check_Record_Representation_Clause
12231 Rectype
:= Entity
(Ident
);
12233 if Rectype
= Any_Type
then
12237 Rectype
:= Underlying_Type
(Rectype
);
12239 -- See if we have a fully repped derived tagged type
12242 PS
: constant Entity_Id
:= Parent_Subtype
(Rectype
);
12245 if Present
(PS
) and then Known_Static_RM_Size
(PS
) then
12246 Tagged_Parent
:= PS
;
12247 Parent_Last_Bit
:= RM_Size
(PS
) - 1;
12249 elsif Present
(PS
) and then Is_Fully_Repped_Tagged_Type
(PS
) then
12250 Tagged_Parent
:= PS
;
12252 -- Find maximum bit of any component of the parent type
12254 Parent_Last_Bit
:= UI_From_Int
(System_Address_Size
- 1);
12255 Pcomp
:= First_Component_Or_Discriminant
(Tagged_Parent
);
12256 while Present
(Pcomp
) loop
12257 if Present
(Component_Bit_Offset
(Pcomp
))
12258 and then Known_Static_Esize
(Pcomp
)
12263 Component_Bit_Offset
(Pcomp
) + Esize
(Pcomp
) - 1);
12266 Next_Component_Or_Discriminant
(Pcomp
);
12271 -- All done if no component clauses
12273 CC
:= First
(Component_Clauses
(N
));
12279 -- If a tag is present, then create a component clause that places it
12280 -- at the start of the record (otherwise gigi may place it after other
12281 -- fields that have rep clauses).
12283 Fent
:= First_Entity
(Rectype
);
12285 if Nkind
(Fent
) = N_Defining_Identifier
12286 and then Chars
(Fent
) = Name_uTag
12288 Set_Component_Bit_Offset
(Fent
, Uint_0
);
12289 Set_Normalized_Position
(Fent
, Uint_0
);
12290 Set_Normalized_First_Bit
(Fent
, Uint_0
);
12291 Set_Esize
(Fent
, UI_From_Int
(System_Address_Size
));
12293 Set_Component_Clause
(Fent
,
12294 Make_Component_Clause
(Loc
,
12295 Component_Name
=> Make_Identifier
(Loc
, Name_uTag
),
12297 Position
=> Make_Integer_Literal
(Loc
, Uint_0
),
12298 First_Bit
=> Make_Integer_Literal
(Loc
, Uint_0
),
12300 Make_Integer_Literal
(Loc
,
12301 UI_From_Int
(System_Address_Size
- 1))));
12303 Ccount
:= Ccount
+ 1;
12306 Max_Bit_So_Far
:= Uint_Minus_1
;
12307 Overlap_Check_Required
:= False;
12309 -- Process the component clauses
12311 while Present
(CC
) loop
12314 if Present
(Comp
) then
12315 Ccount
:= Ccount
+ 1;
12317 -- We need a full overlap check if record positions non-monotonic
12319 if Fbit
<= Max_Bit_So_Far
then
12320 Overlap_Check_Required
:= True;
12323 Max_Bit_So_Far
:= Lbit
;
12325 -- Check bit position out of range of specified size
12327 if Has_Size_Clause
(Rectype
)
12328 and then RM_Size
(Rectype
) <= Lbit
12330 Error_Msg_Uint_1
:= RM_Size
(Rectype
);
12331 Error_Msg_Uint_2
:= Lbit
+ 1;
12332 Error_Msg_N
("bit number out of range of specified "
12333 & "size (expected ^, got ^)",
12336 -- Check for overlap with tag or parent component
12339 if Is_Tagged_Type
(Rectype
)
12340 and then Fbit
< System_Address_Size
12343 ("component overlaps tag field of&",
12344 Component_Name
(CC
), Rectype
);
12345 Overlap_Detected
:= True;
12347 elsif Present
(Tagged_Parent
)
12348 and then Fbit
<= Parent_Last_Bit
12351 ("component overlaps parent field of&",
12352 Component_Name
(CC
), Rectype
);
12353 Overlap_Detected
:= True;
12356 if Hbit
< Lbit
then
12365 -- Now that we have processed all the component clauses, check for
12366 -- overlap. We have to leave this till last, since the components can
12367 -- appear in any arbitrary order in the representation clause.
12369 -- We do not need this check if all specified ranges were monotonic,
12370 -- as recorded by Overlap_Check_Required being False at this stage.
12372 -- This first section checks if there are any overlapping entries at
12373 -- all. It does this by sorting all entries and then seeing if there are
12374 -- any overlaps. If there are none, then that is decisive, but if there
12375 -- are overlaps, they may still be OK (they may result from fields in
12376 -- different variants).
12378 if Overlap_Check_Required
then
12379 Overlap_Check1
: declare
12381 OC_Fbit
: array (0 .. Ccount
) of Uint
;
12382 -- First-bit values for component clauses, the value is the offset
12383 -- of the first bit of the field from start of record. The zero
12384 -- entry is for use in sorting.
12386 OC_Lbit
: array (0 .. Ccount
) of Uint
;
12387 -- Last-bit values for component clauses, the value is the offset
12388 -- of the last bit of the field from start of record. The zero
12389 -- entry is for use in sorting.
12391 OC_Count
: Natural := 0;
12392 -- Count of entries in OC_Fbit and OC_Lbit
12394 function OC_Lt
(Op1
, Op2
: Natural) return Boolean;
12395 -- Compare routine for Sort
12397 procedure OC_Move
(From
: Natural; To
: Natural);
12398 -- Move routine for Sort
12400 package Sorting
is new GNAT
.Heap_Sort_G
(OC_Move
, OC_Lt
);
12406 function OC_Lt
(Op1
, Op2
: Natural) return Boolean is
12408 return OC_Fbit
(Op1
) < OC_Fbit
(Op2
);
12415 procedure OC_Move
(From
: Natural; To
: Natural) is
12417 OC_Fbit
(To
) := OC_Fbit
(From
);
12418 OC_Lbit
(To
) := OC_Lbit
(From
);
12421 -- Start of processing for Overlap_Check
12424 CC
:= First
(Component_Clauses
(N
));
12425 while Present
(CC
) loop
12427 -- Exclude component clause already marked in error
12429 if not Error_Posted
(CC
) then
12432 if Present
(Comp
) then
12433 OC_Count
:= OC_Count
+ 1;
12434 OC_Fbit
(OC_Count
) := Fbit
;
12435 OC_Lbit
(OC_Count
) := Lbit
;
12442 Sorting
.Sort
(OC_Count
);
12444 Overlap_Check_Required
:= False;
12445 for J
in 1 .. OC_Count
- 1 loop
12446 if OC_Lbit
(J
) >= OC_Fbit
(J
+ 1) then
12447 Overlap_Check_Required
:= True;
12451 end Overlap_Check1
;
12454 -- If Overlap_Check_Required is still True, then we have to do the full
12455 -- scale overlap check, since we have at least two fields that do
12456 -- overlap, and we need to know if that is OK since they are in
12457 -- different variant, or whether we have a definite problem.
12459 if Overlap_Check_Required
then
12460 Overlap_Check2
: declare
12461 C1_Ent
, C2_Ent
: Entity_Id
;
12462 -- Entities of components being checked for overlap
12465 -- Component_List node whose Component_Items are being checked
12468 -- Component declaration for component being checked
12471 C1_Ent
:= First_Entity
(Base_Type
(Rectype
));
12473 -- Loop through all components in record. For each component check
12474 -- for overlap with any of the preceding elements on the component
12475 -- list containing the component and also, if the component is in
12476 -- a variant, check against components outside the case structure.
12477 -- This latter test is repeated recursively up the variant tree.
12479 Main_Component_Loop
: while Present
(C1_Ent
) loop
12480 if Ekind
(C1_Ent
) not in E_Component | E_Discriminant
then
12481 goto Continue_Main_Component_Loop
;
12484 -- Skip overlap check if entity has no declaration node. This
12485 -- happens with discriminants in constrained derived types.
12486 -- Possibly we are missing some checks as a result, but that
12487 -- does not seem terribly serious.
12489 if No
(Declaration_Node
(C1_Ent
)) then
12490 goto Continue_Main_Component_Loop
;
12493 Clist
:= Parent
(List_Containing
(Declaration_Node
(C1_Ent
)));
12495 -- Loop through component lists that need checking. Check the
12496 -- current component list and all lists in variants above us.
12498 Component_List_Loop
: loop
12500 -- If derived type definition, go to full declaration
12501 -- If at outer level, check discriminants if there are any.
12503 if Nkind
(Clist
) = N_Derived_Type_Definition
then
12504 Clist
:= Parent
(Clist
);
12507 -- Outer level of record definition, check discriminants
12508 -- but be careful not to flag a non-stored discriminant
12509 -- and the stored discriminant it renames as overlapping.
12511 if Nkind
(Clist
) in N_Full_Type_Declaration
12512 | N_Private_Type_Declaration
12514 if Has_Discriminants
(Defining_Identifier
(Clist
)) then
12516 First_Discriminant
(Defining_Identifier
(Clist
));
12517 while Present
(C2_Ent
) loop
12519 Original_Record_Component
(C1_Ent
) =
12520 Original_Record_Component
(C2_Ent
);
12521 Check_Component_Overlap
(C1_Ent
, C2_Ent
);
12522 Next_Discriminant
(C2_Ent
);
12526 -- Record extension case
12528 elsif Nkind
(Clist
) = N_Derived_Type_Definition
then
12531 -- Otherwise check one component list
12534 Citem
:= First
(Component_Items
(Clist
));
12535 while Present
(Citem
) loop
12536 if Nkind
(Citem
) = N_Component_Declaration
then
12537 C2_Ent
:= Defining_Identifier
(Citem
);
12538 exit when C1_Ent
= C2_Ent
;
12539 Check_Component_Overlap
(C1_Ent
, C2_Ent
);
12546 -- Check for variants above us (the parent of the Clist can
12547 -- be a variant, in which case its parent is a variant part,
12548 -- and the parent of the variant part is a component list
12549 -- whose components must all be checked against the current
12550 -- component for overlap).
12552 if Nkind
(Parent
(Clist
)) = N_Variant
then
12553 Clist
:= Parent
(Parent
(Parent
(Clist
)));
12555 -- Check for possible discriminant part in record, this
12556 -- is treated essentially as another level in the
12557 -- recursion. For this case the parent of the component
12558 -- list is the record definition, and its parent is the
12559 -- full type declaration containing the discriminant
12562 elsif Nkind
(Parent
(Clist
)) = N_Record_Definition
then
12563 Clist
:= Parent
(Parent
((Clist
)));
12565 -- If neither of these two cases, we are at the top of
12569 exit Component_List_Loop
;
12571 end loop Component_List_Loop
;
12573 <<Continue_Main_Component_Loop
>>
12574 Next_Entity
(C1_Ent
);
12576 end loop Main_Component_Loop
;
12577 end Overlap_Check2
;
12580 -- Skip the following warnings if overlap was detected; programmer
12581 -- should fix the errors first. Also skip the warnings for types in
12582 -- generics, because their representation information is not fully
12585 if not Overlap_Detected
and then not In_Generic_Scope
(Rectype
) then
12586 -- Check for record holes (gaps)
12588 if Warn_On_Record_Holes
then
12592 Record_Hole_Check
(Rectype
, After_Last
=> Ignore
, Warn
=> True);
12596 -- Check for out-of-order component clauses
12598 if Warn_On_Component_Order
then
12599 Component_Order_Check
(Rectype
);
12603 -- For records that have component clauses for all components, and whose
12604 -- size is less than or equal to 32, and which can be fully packed, we
12605 -- need to know the size in the front end to activate possible packed
12606 -- array processing where the component type is a record.
12608 -- At this stage Hbit + 1 represents the first unused bit from all the
12609 -- component clauses processed, so if the component clauses are
12610 -- complete, then this is the length of the record.
12612 -- For records longer than System.Storage_Unit, and for those where not
12613 -- all components have component clauses, the back end determines the
12614 -- length (it may for example be appropriate to round up the size
12615 -- to some convenient boundary, based on alignment considerations, etc).
12617 if not Known_RM_Size
(Rectype
)
12618 and then Hbit
+ 1 <= 32
12619 and then not Strict_Alignment
(Rectype
)
12622 -- Nothing to do if at least one component has no component clause
12624 Comp
:= First_Component_Or_Discriminant
(Rectype
);
12625 while Present
(Comp
) loop
12626 exit when No
(Component_Clause
(Comp
));
12627 Next_Component_Or_Discriminant
(Comp
);
12630 -- If we fall out of loop, all components have component clauses
12631 -- and so we can set the size to the maximum value.
12634 Set_RM_Size
(Rectype
, Hbit
+ 1);
12637 end Check_Record_Representation_Clause
;
12643 procedure Check_Size
12647 Biased
: out Boolean)
12649 procedure Size_Too_Small_Error
(Min_Siz
: Uint
);
12650 -- Emit an error concerning illegal size Siz. Min_Siz denotes the
12653 --------------------------
12654 -- Size_Too_Small_Error --
12655 --------------------------
12657 procedure Size_Too_Small_Error
(Min_Siz
: Uint
) is
12659 Error_Msg_Uint_1
:= Min_Siz
;
12660 Error_Msg_NE
(Size_Too_Small_Message
, N
, T
);
12661 end Size_Too_Small_Error
;
12665 UT
: constant Entity_Id
:= Underlying_Type
(T
);
12668 -- Start of processing for Check_Size
12673 -- Reject patently improper size values
12675 if Is_Elementary_Type
(T
)
12676 and then Siz
> Int
'Last
12678 Error_Msg_N
("Size value too large for elementary type", N
);
12680 if Nkind
(Original_Node
(N
)) = N_Op_Expon
then
12682 ("\maybe '* was meant, rather than '*'*", Original_Node
(N
));
12686 -- Dismiss generic types
12688 if Is_Generic_Type
(T
)
12690 Is_Generic_Type
(UT
)
12692 Is_Generic_Type
(Root_Type
(UT
))
12696 -- Guard against previous errors
12698 elsif No
(UT
) or else UT
= Any_Type
then
12699 Check_Error_Detected
;
12702 -- Check case of bit packed array
12704 elsif Is_Array_Type
(UT
)
12705 and then Known_Static_Component_Size
(UT
)
12706 and then Is_Bit_Packed_Array
(UT
)
12714 Asiz
:= Component_Size
(UT
);
12715 Indx
:= First_Index
(UT
);
12717 Ityp
:= Etype
(Indx
);
12719 -- If non-static bound, then we are not in the business of
12720 -- trying to check the length, and indeed an error will be
12721 -- issued elsewhere, since sizes of non-static array types
12722 -- cannot be set implicitly or explicitly.
12724 if not Is_OK_Static_Subtype
(Ityp
) then
12728 -- Otherwise accumulate next dimension
12730 Asiz
:= Asiz
* (Expr_Value
(Type_High_Bound
(Ityp
)) -
12731 Expr_Value
(Type_Low_Bound
(Ityp
)) +
12735 exit when No
(Indx
);
12738 if Asiz
<= Siz
then
12742 Size_Too_Small_Error
(Asiz
);
12746 -- All other composite types are ignored
12748 elsif Is_Composite_Type
(UT
) then
12751 -- For fixed-point types, don't check minimum if type is not frozen,
12752 -- since we don't know all the characteristics of the type that can
12753 -- affect the size (e.g. a specified small) till freeze time.
12755 elsif Is_Fixed_Point_Type
(UT
) and then not Is_Frozen
(UT
) then
12758 -- Cases for which a minimum check is required
12761 -- Ignore if specified size is correct for the type
12763 if Known_Esize
(UT
) and then Siz
= Esize
(UT
) then
12767 -- Otherwise get minimum size
12769 M
:= UI_From_Int
(Minimum_Size
(UT
));
12773 -- Size is less than minimum size, but one possibility remains
12774 -- that we can manage with the new size if we bias the type.
12776 M
:= UI_From_Int
(Minimum_Size
(UT
, Biased
=> True));
12779 Size_Too_Small_Error
(M
);
12787 --------------------------
12788 -- Freeze_Entity_Checks --
12789 --------------------------
12791 procedure Freeze_Entity_Checks
(N
: Node_Id
) is
12792 procedure Hide_Non_Overridden_Subprograms
(Typ
: Entity_Id
);
12793 -- Inspect the primitive operations of type Typ and hide all pairs of
12794 -- implicitly declared non-overridden non-fully conformant homographs
12795 -- (Ada RM 8.3 12.3/2).
12797 -------------------------------------
12798 -- Hide_Non_Overridden_Subprograms --
12799 -------------------------------------
12801 procedure Hide_Non_Overridden_Subprograms
(Typ
: Entity_Id
) is
12802 procedure Hide_Matching_Homographs
12803 (Subp_Id
: Entity_Id
;
12804 Start_Elmt
: Elmt_Id
);
12805 -- Inspect a list of primitive operations starting with Start_Elmt
12806 -- and find matching implicitly declared non-overridden non-fully
12807 -- conformant homographs of Subp_Id. If found, all matches along
12808 -- with Subp_Id are hidden from all visibility.
12810 function Is_Non_Overridden_Or_Null_Procedure
12811 (Subp_Id
: Entity_Id
) return Boolean;
12812 -- Determine whether subprogram Subp_Id is implicitly declared non-
12813 -- overridden subprogram or an implicitly declared null procedure.
12815 ------------------------------
12816 -- Hide_Matching_Homographs --
12817 ------------------------------
12819 procedure Hide_Matching_Homographs
12820 (Subp_Id
: Entity_Id
;
12821 Start_Elmt
: Elmt_Id
)
12824 Prim_Elmt
: Elmt_Id
;
12827 Prim_Elmt
:= Start_Elmt
;
12828 while Present
(Prim_Elmt
) loop
12829 Prim
:= Node
(Prim_Elmt
);
12831 -- The current primitive is implicitly declared non-overridden
12832 -- non-fully conformant homograph of Subp_Id. Both subprograms
12833 -- must be hidden from visibility.
12835 if Chars
(Prim
) = Chars
(Subp_Id
)
12836 and then Is_Non_Overridden_Or_Null_Procedure
(Prim
)
12837 and then not Fully_Conformant
(Prim
, Subp_Id
)
12839 Set_Is_Hidden_Non_Overridden_Subpgm
(Prim
);
12840 Set_Is_Immediately_Visible
(Prim
, False);
12841 Set_Is_Potentially_Use_Visible
(Prim
, False);
12843 Set_Is_Hidden_Non_Overridden_Subpgm
(Subp_Id
);
12844 Set_Is_Immediately_Visible
(Subp_Id
, False);
12845 Set_Is_Potentially_Use_Visible
(Subp_Id
, False);
12848 Next_Elmt
(Prim_Elmt
);
12850 end Hide_Matching_Homographs
;
12852 -----------------------------------------
12853 -- Is_Non_Overridden_Or_Null_Procedure --
12854 -----------------------------------------
12856 function Is_Non_Overridden_Or_Null_Procedure
12857 (Subp_Id
: Entity_Id
) return Boolean
12859 Alias_Id
: Entity_Id
;
12862 -- The subprogram is inherited (implicitly declared), it does not
12863 -- override and does not cover a primitive of an interface.
12865 if Ekind
(Subp_Id
) in E_Function | E_Procedure
12866 and then Present
(Alias
(Subp_Id
))
12867 and then No
(Interface_Alias
(Subp_Id
))
12868 and then No
(Overridden_Operation
(Subp_Id
))
12870 Alias_Id
:= Alias
(Subp_Id
);
12872 if Requires_Overriding
(Alias_Id
) then
12875 elsif Nkind
(Parent
(Alias_Id
)) = N_Procedure_Specification
12876 and then Null_Present
(Parent
(Alias_Id
))
12883 end Is_Non_Overridden_Or_Null_Procedure
;
12887 Prim_Ops
: constant Elist_Id
:= Direct_Primitive_Operations
(Typ
);
12889 Prim_Elmt
: Elmt_Id
;
12891 -- Start of processing for Hide_Non_Overridden_Subprograms
12894 -- Inspect the list of primitives looking for non-overridden
12897 if Present
(Prim_Ops
) then
12898 Prim_Elmt
:= First_Elmt
(Prim_Ops
);
12899 while Present
(Prim_Elmt
) loop
12900 Prim
:= Node
(Prim_Elmt
);
12901 Next_Elmt
(Prim_Elmt
);
12903 if Is_Non_Overridden_Or_Null_Procedure
(Prim
) then
12904 Hide_Matching_Homographs
12906 Start_Elmt
=> Prim_Elmt
);
12910 end Hide_Non_Overridden_Subprograms
;
12914 E
: constant Entity_Id
:= Entity
(N
);
12916 Nongeneric_Case
: constant Boolean := Nkind
(N
) = N_Freeze_Entity
;
12917 -- True in nongeneric case. Some of the processing here is skipped
12918 -- for the generic case since it is not needed. Basically in the
12919 -- generic case, we only need to do stuff that might generate error
12920 -- messages or warnings.
12922 -- Start of processing for Freeze_Entity_Checks
12925 -- Remember that we are processing a freezing entity. Required to
12926 -- ensure correct decoration of internal entities associated with
12927 -- interfaces (see New_Overloaded_Entity).
12929 Inside_Freezing_Actions
:= Inside_Freezing_Actions
+ 1;
12931 -- For tagged types covering interfaces add internal entities that link
12932 -- the primitives of the interfaces with the primitives that cover them.
12933 -- Note: These entities were originally generated only when generating
12934 -- code because their main purpose was to provide support to initialize
12935 -- the secondary dispatch tables. They are also used to locate
12936 -- primitives covering interfaces when processing generics (see
12937 -- Derive_Subprograms).
12939 -- This is not needed in the generic case
12941 if Ada_Version
>= Ada_2005
12942 and then Nongeneric_Case
12943 and then Ekind
(E
) = E_Record_Type
12944 and then Is_Tagged_Type
(E
)
12945 and then not Is_Interface
(E
)
12946 and then Has_Interfaces
(E
)
12948 -- This would be a good common place to call the routine that checks
12949 -- overriding of interface primitives (and thus factorize calls to
12950 -- Check_Abstract_Overriding located at different contexts in the
12951 -- compiler). However, this is not possible because it causes
12952 -- spurious errors in case of late overriding.
12954 Add_Internal_Interface_Entities
(E
);
12957 -- After all forms of overriding have been resolved, a tagged type may
12958 -- be left with a set of implicitly declared and possibly erroneous
12959 -- abstract subprograms, null procedures and subprograms that require
12960 -- overriding. If this set contains fully conformant homographs, then
12961 -- one is chosen arbitrarily (already done during resolution), otherwise
12962 -- all remaining non-fully conformant homographs are hidden from
12963 -- visibility (Ada RM 8.3 12.3/2).
12965 if Is_Tagged_Type
(E
) then
12966 Hide_Non_Overridden_Subprograms
(E
);
12971 if Ekind
(E
) = E_Record_Type
12972 and then Is_CPP_Class
(E
)
12973 and then Is_Tagged_Type
(E
)
12974 and then Tagged_Type_Expansion
12976 if CPP_Num_Prims
(E
) = 0 then
12978 -- If the CPP type has user defined components then it must import
12979 -- primitives from C++. This is required because if the C++ class
12980 -- has no primitives then the C++ compiler does not added the _tag
12981 -- component to the type.
12983 if First_Entity
(E
) /= Last_Entity
(E
) then
12985 ("'C'P'P type must import at least one primitive from C++??",
12990 -- Check that all its primitives are abstract or imported from C++.
12991 -- Check also availability of the C++ constructor.
12994 Has_Constructors
: constant Boolean := Has_CPP_Constructors
(E
);
12996 Error_Reported
: Boolean := False;
13000 Elmt
:= First_Elmt
(Primitive_Operations
(E
));
13001 while Present
(Elmt
) loop
13002 Prim
:= Node
(Elmt
);
13004 if Comes_From_Source
(Prim
) then
13005 if Is_Abstract_Subprogram
(Prim
) then
13008 elsif not Is_Imported
(Prim
)
13009 or else Convention
(Prim
) /= Convention_CPP
13012 ("primitives of 'C'P'P types must be imported from C++ "
13013 & "or abstract??", Prim
);
13015 elsif not Has_Constructors
13016 and then not Error_Reported
13018 Error_Msg_Name_1
:= Chars
(E
);
13020 ("??'C'P'P constructor required for type %", Prim
);
13021 Error_Reported
:= True;
13030 -- Check Ada derivation of CPP type
13032 if Expander_Active
-- why? losing errors in -gnatc mode???
13033 and then Present
(Etype
(E
)) -- defend against errors
13034 and then Tagged_Type_Expansion
13035 and then Ekind
(E
) = E_Record_Type
13036 and then Etype
(E
) /= E
13037 and then Is_CPP_Class
(Etype
(E
))
13038 and then CPP_Num_Prims
(Etype
(E
)) > 0
13039 and then not Is_CPP_Class
(E
)
13040 and then not Has_CPP_Constructors
(Etype
(E
))
13042 -- If the parent has C++ primitives but it has no constructor then
13043 -- check that all the primitives are overridden in this derivation;
13044 -- otherwise the constructor of the parent is needed to build the
13052 Elmt
:= First_Elmt
(Primitive_Operations
(E
));
13053 while Present
(Elmt
) loop
13054 Prim
:= Node
(Elmt
);
13056 if not Is_Abstract_Subprogram
(Prim
)
13057 and then No
(Interface_Alias
(Prim
))
13058 and then Find_Dispatching_Type
(Ultimate_Alias
(Prim
)) /= E
13060 Error_Msg_Name_1
:= Chars
(Etype
(E
));
13062 ("'C'P'P constructor required for parent type %", E
);
13071 Inside_Freezing_Actions
:= Inside_Freezing_Actions
- 1;
13073 -- For a record type, deal with variant parts. This has to be delayed to
13074 -- this point, because of the issue of statically predicated subtypes,
13075 -- which we have to ensure are frozen before checking choices, since we
13076 -- need to have the static choice list set.
13078 if Is_Record_Type
(E
) then
13079 Check_Variant_Part
: declare
13080 D
: constant Node_Id
:= Declaration_Node
(E
);
13085 Others_Present
: Boolean;
13086 pragma Warnings
(Off
, Others_Present
);
13087 -- Indicates others present, not used in this case
13089 procedure Non_Static_Choice_Error
(Choice
: Node_Id
);
13090 -- Error routine invoked by the generic instantiation below when
13091 -- the variant part has a non static choice.
13093 procedure Process_Declarations
(Variant
: Node_Id
);
13094 -- Processes declarations associated with a variant. We analyzed
13095 -- the declarations earlier (in Sem_Ch3.Analyze_Variant_Part),
13096 -- but we still need the recursive call to Check_Choices for any
13097 -- nested variant to get its choices properly processed. This is
13098 -- also where we expand out the choices if expansion is active.
13100 package Variant_Choices_Processing
is new
13101 Generic_Check_Choices
13102 (Process_Empty_Choice
=> No_OP
,
13103 Process_Non_Static_Choice
=> Non_Static_Choice_Error
,
13104 Process_Associated_Node
=> Process_Declarations
);
13105 use Variant_Choices_Processing
;
13107 -----------------------------
13108 -- Non_Static_Choice_Error --
13109 -----------------------------
13111 procedure Non_Static_Choice_Error
(Choice
: Node_Id
) is
13113 Flag_Non_Static_Expr
13114 ("choice given in variant part is not static!", Choice
);
13115 end Non_Static_Choice_Error
;
13117 --------------------------
13118 -- Process_Declarations --
13119 --------------------------
13121 procedure Process_Declarations
(Variant
: Node_Id
) is
13122 CL
: constant Node_Id
:= Component_List
(Variant
);
13126 -- Check for static predicate present in this variant
13128 if Has_SP_Choice
(Variant
) then
13130 -- Here we expand. You might expect to find this call in
13131 -- Expand_N_Variant_Part, but that is called when we first
13132 -- see the variant part, and we cannot do this expansion
13133 -- earlier than the freeze point, since for statically
13134 -- predicated subtypes, the predicate is not known till
13135 -- the freeze point.
13137 -- Furthermore, we do this expansion even if the expander
13138 -- is not active, because other semantic processing, e.g.
13139 -- for aggregates, requires the expanded list of choices.
13141 -- If the expander is not active, then we can't just clobber
13142 -- the list since it would invalidate the tree.
13143 -- So we have to rewrite the variant part with a Rewrite
13144 -- call that replaces it with a copy and clobber the copy.
13146 if not Expander_Active
then
13148 NewV
: constant Node_Id
:= New_Copy
(Variant
);
13150 Set_Discrete_Choices
13151 (NewV
, New_Copy_List
(Discrete_Choices
(Variant
)));
13152 Rewrite
(Variant
, NewV
);
13156 Expand_Static_Predicates_In_Choices
(Variant
);
13159 -- We don't need to worry about the declarations in the variant
13160 -- (since they were analyzed by Analyze_Choices when we first
13161 -- encountered the variant), but we do need to take care of
13162 -- expansion of any nested variants.
13164 if not Null_Present
(CL
) then
13165 VP
:= Variant_Part
(CL
);
13167 if Present
(VP
) then
13169 (VP
, Variants
(VP
), Etype
(Name
(VP
)), Others_Present
);
13172 end Process_Declarations
;
13174 -- Start of processing for Check_Variant_Part
13177 -- Find component list
13181 if Nkind
(D
) = N_Full_Type_Declaration
then
13182 T
:= Type_Definition
(D
);
13184 if Nkind
(T
) = N_Record_Definition
then
13185 C
:= Component_List
(T
);
13187 elsif Nkind
(T
) = N_Derived_Type_Definition
13188 and then Present
(Record_Extension_Part
(T
))
13190 C
:= Component_List
(Record_Extension_Part
(T
));
13194 -- Case of variant part present
13196 if Present
(C
) and then Present
(Variant_Part
(C
)) then
13197 VP
:= Variant_Part
(C
);
13202 (VP
, Variants
(VP
), Etype
(Name
(VP
)), Others_Present
);
13204 -- If the last variant does not contain the Others choice,
13205 -- replace it with an N_Others_Choice node since Gigi always
13206 -- wants an Others. Note that we do not bother to call Analyze
13207 -- on the modified variant part, since its only effect would be
13208 -- to compute the Others_Discrete_Choices node laboriously, and
13209 -- of course we already know the list of choices corresponding
13210 -- to the others choice (it's the list we're replacing).
13212 -- We only want to do this if the expander is active, since
13213 -- we do not want to clobber the tree.
13215 if Expander_Active
then
13217 Last_Var
: constant Node_Id
:=
13218 Last_Non_Pragma
(Variants
(VP
));
13220 Others_Node
: Node_Id
;
13223 if Nkind
(First
(Discrete_Choices
(Last_Var
))) /=
13226 Others_Node
:= Make_Others_Choice
(Sloc
(Last_Var
));
13227 Set_Others_Discrete_Choices
13228 (Others_Node
, Discrete_Choices
(Last_Var
));
13229 Set_Discrete_Choices
13230 (Last_Var
, New_List
(Others_Node
));
13235 end Check_Variant_Part
;
13238 -- If we have a type with predicates, build predicate function. This is
13239 -- not needed in the generic case, nor within e.g. TSS subprograms and
13240 -- other predefined primitives. For a derived type, ensure that the
13241 -- parent type is already frozen so that its predicate function has been
13242 -- constructed already. This is necessary if the parent is declared
13243 -- in a nested package and its own freeze point has not been reached.
13246 and then Nongeneric_Case
13247 and then Has_Predicates
(E
)
13248 and then Predicate_Check_In_Scope
(N
)
13251 Atyp
: constant Entity_Id
:= Nearest_Ancestor
(E
);
13255 and then Has_Predicates
(Atyp
)
13256 and then not Is_Frozen
(Atyp
)
13258 Freeze_Before
(N
, Atyp
);
13262 -- Before we build a predicate function, ensure that discriminant
13263 -- checking functions are available. The predicate function might
13264 -- need to call these functions if the predicate references any
13265 -- components declared in a variant part.
13267 if Ekind
(E
) = E_Record_Type
and then Has_Discriminants
(E
) then
13268 Build_Or_Copy_Discr_Checking_Funcs
(Parent
(E
));
13271 Build_Predicate_Function
(E
, N
);
13274 -- If type has delayed aspects, this is where we do the preanalysis at
13275 -- the freeze point, as part of the consistent visibility check. Note
13276 -- that this must be done after calling Build_Predicate_Function or
13277 -- Build_Invariant_Procedure since these subprograms fix occurrences of
13278 -- the subtype name in the saved expression so that they will not cause
13279 -- trouble in the preanalysis.
13281 -- This is also not needed in the generic case
13284 and then Has_Delayed_Aspects
(E
)
13285 and then Scope
(E
) = Current_Scope
13291 -- Look for aspect specification entries for this entity
13293 Ritem
:= First_Rep_Item
(E
);
13294 while Present
(Ritem
) loop
13295 if Nkind
(Ritem
) = N_Aspect_Specification
13296 and then Entity
(Ritem
) = E
13297 and then Is_Delayed_Aspect
(Ritem
)
13299 if Get_Aspect_Id
(Ritem
) in Aspect_CPU
13300 | Aspect_Dynamic_Predicate
13301 | Aspect_Ghost_Predicate
13303 | Aspect_Static_Predicate
13306 -- Retrieve the visibility to components and discriminants
13307 -- in order to properly analyze the aspects.
13310 Check_Aspect_At_Freeze_Point
(Ritem
);
13312 -- In the case of predicate aspects, there will be
13313 -- a corresponding Predicate pragma associated with
13314 -- the aspect, and the expression of the pragma also
13315 -- needs to be analyzed at this point, to ensure that
13316 -- Save_Global_References will capture global refs in
13317 -- expressions that occur in generic bodies, for proper
13318 -- later resolution of the pragma in instantiations.
13321 and then Inside_A_Generic
13322 and then Has_Predicates
(E
)
13323 and then Present
(Aspect_Rep_Item
(Ritem
))
13326 Pragma_Args
: constant List_Id
:=
13327 Pragma_Argument_Associations
13328 (Aspect_Rep_Item
(Ritem
));
13329 Pragma_Expr
: constant Node_Id
:=
13330 Expression
(Next
(First
(Pragma_Args
)));
13332 if Present
(Pragma_Expr
) then
13333 Analyze_And_Resolve
13334 (Pragma_Expr
, Standard_Boolean
);
13342 Check_Aspect_At_Freeze_Point
(Ritem
);
13345 -- A pragma Predicate should be checked like one of the
13346 -- corresponding aspects, wrt possible misuse of ghost
13349 elsif Nkind
(Ritem
) = N_Pragma
13350 and then No
(Corresponding_Aspect
(Ritem
))
13352 Get_Pragma_Id
(Pragma_Name
(Ritem
)) = Pragma_Predicate
13354 -- Retrieve the visibility to components and discriminants
13355 -- in order to properly analyze the pragma.
13358 Arg
: constant Node_Id
:=
13359 Next
(First
(Pragma_Argument_Associations
(Ritem
)));
13362 Preanalyze_Spec_Expression
13363 (Expression
(Arg
), Standard_Boolean
);
13368 Next_Rep_Item
(Ritem
);
13373 if not In_Generic_Scope
(E
)
13374 and then Ekind
(E
) = E_Record_Type
13375 and then Is_Tagged_Type
(E
)
13377 Process_Class_Conditions_At_Freeze_Point
(E
);
13379 end Freeze_Entity_Checks
;
13381 -------------------------
13382 -- Get_Alignment_Value --
13383 -------------------------
13385 function Get_Alignment_Value
(Expr
: Node_Id
) return Uint
is
13386 Align
: constant Uint
:= Static_Integer
(Expr
);
13392 elsif Align
< 0 then
13393 Error_Msg_N
("alignment value must be positive", Expr
);
13396 -- If Alignment is specified to be 0, we treat it the same as 1
13398 elsif Align
= 0 then
13402 for J
in Int
range 0 .. 64 loop
13404 M
: constant Uint
:= Uint_2
** J
;
13407 exit when M
= Align
;
13410 Error_Msg_N
("alignment value must be power of 2", Expr
);
13418 end Get_Alignment_Value
;
13420 -----------------------------------
13421 -- Has_Compatible_Representation --
13422 -----------------------------------
13424 function Has_Compatible_Representation
13425 (Target_Typ
, Operand_Typ
: Entity_Id
) return Boolean
13427 -- The subtype-specific representation attributes (Size and Alignment)
13428 -- do not affect representation from the point of view of this function.
13430 T1
: constant Entity_Id
:= Implementation_Base_Type
(Target_Typ
);
13431 T2
: constant Entity_Id
:= Implementation_Base_Type
(Operand_Typ
);
13434 -- Return true immediately for the same base type
13439 -- Tagged types always have the same representation, because it is not
13440 -- possible to specify different representations for common fields.
13442 elsif Is_Tagged_Type
(T1
) then
13445 -- Representations are definitely different if conventions differ
13447 elsif Convention
(T1
) /= Convention
(T2
) then
13450 -- Representations are different if component alignments or scalar
13451 -- storage orders differ.
13453 elsif (Is_Record_Type
(T1
) or else Is_Array_Type
(T1
))
13455 (Is_Record_Type
(T2
) or else Is_Array_Type
(T2
))
13456 and then (Component_Alignment
(T1
) /= Component_Alignment
(T2
)
13458 Reverse_Storage_Order
(T1
) /= Reverse_Storage_Order
(T2
))
13463 -- For arrays, the only real issue is component size. If we know the
13464 -- component size for both arrays, and it is the same, then that's
13465 -- good enough to know we don't have a change of representation.
13467 if Is_Array_Type
(T1
) then
13469 -- In a view conversion, if the target type is an array type having
13470 -- aliased components and the operand type is an array type having
13471 -- unaliased components, then a new object is created (4.6(58.3/4)).
13473 if Has_Aliased_Components
(T1
)
13474 and then not Has_Aliased_Components
(T2
)
13479 if Known_Component_Size
(T1
)
13480 and then Known_Component_Size
(T2
)
13481 and then Component_Size
(T1
) = Component_Size
(T2
)
13486 -- For records, representations are different if reordering differs
13488 elsif Is_Record_Type
(T1
)
13489 and then Is_Record_Type
(T2
)
13490 and then No_Reordering
(T1
) /= No_Reordering
(T2
)
13495 -- Types definitely have same representation if neither has non-standard
13496 -- representation since default representations are always consistent.
13497 -- If only one has non-standard representation, and the other does not,
13498 -- then we consider that they do not have the same representation. They
13499 -- might, but there is no way of telling early enough.
13501 if Has_Non_Standard_Rep
(T1
) then
13502 if not Has_Non_Standard_Rep
(T2
) then
13506 return not Has_Non_Standard_Rep
(T2
);
13509 -- Here the two types both have non-standard representation, and we need
13510 -- to determine if they have the same non-standard representation.
13512 -- For arrays, we simply need to test if the component sizes are the
13513 -- same. Pragma Pack is reflected in modified component sizes, so this
13514 -- check also deals with pragma Pack.
13516 if Is_Array_Type
(T1
) then
13517 return Component_Size
(T1
) = Component_Size
(T2
);
13519 -- Case of record types
13521 elsif Is_Record_Type
(T1
) then
13523 -- Packed status must conform
13525 if Is_Packed
(T1
) /= Is_Packed
(T2
) then
13528 -- If the operand type is derived from the target type and no clause
13529 -- has been given after the derivation, then the representations are
13530 -- the same since the derived type inherits that of the parent type.
13532 elsif Is_Derived_Type
(T2
)
13533 and then Etype
(T2
) = T1
13534 and then not Has_Record_Rep_Clause
(T2
)
13538 -- Otherwise we must check components. Typ2 maybe a constrained
13539 -- subtype with fewer components, so we compare the components
13540 -- of the base types.
13543 Record_Case
: declare
13544 CD1
, CD2
: Entity_Id
;
13546 function Same_Rep
return Boolean;
13547 -- CD1 and CD2 are either components or discriminants. This
13548 -- function tests whether they have the same representation.
13554 function Same_Rep
return Boolean is
13556 if No
(Component_Clause
(CD1
)) then
13557 return No
(Component_Clause
(CD2
));
13559 -- Note: at this point, component clauses have been
13560 -- normalized to the default bit order, so that the
13561 -- comparison of Component_Bit_Offsets is meaningful.
13564 Present
(Component_Clause
(CD2
))
13566 Component_Bit_Offset
(CD1
) = Component_Bit_Offset
(CD2
)
13568 Esize
(CD1
) = Esize
(CD2
);
13572 -- Start of processing for Record_Case
13575 if Has_Discriminants
(T1
) then
13577 -- The number of discriminants may be different if the
13578 -- derived type has fewer (constrained by values). The
13579 -- invisible discriminants retain the representation of
13580 -- the original, so the discrepancy does not per se
13581 -- indicate a different representation.
13583 CD1
:= First_Discriminant
(T1
);
13584 CD2
:= First_Discriminant
(T2
);
13585 while Present
(CD1
) and then Present
(CD2
) loop
13586 if not Same_Rep
then
13589 Next_Discriminant
(CD1
);
13590 Next_Discriminant
(CD2
);
13595 CD1
:= First_Component
(Underlying_Type
(Base_Type
(T1
)));
13596 CD2
:= First_Component
(Underlying_Type
(Base_Type
(T2
)));
13597 while Present
(CD1
) loop
13598 if not Same_Rep
then
13601 Next_Component
(CD1
);
13602 Next_Component
(CD2
);
13610 -- For enumeration types, we must check each literal to see if the
13611 -- representation is the same. Note that we do not permit enumeration
13612 -- representation clauses for Character and Wide_Character, so these
13613 -- cases were already dealt with.
13615 elsif Is_Enumeration_Type
(T1
) then
13616 Enumeration_Case
: declare
13617 L1
, L2
: Entity_Id
;
13620 L1
:= First_Literal
(T1
);
13621 L2
:= First_Literal
(T2
);
13622 while Present
(L1
) loop
13623 if Enumeration_Rep
(L1
) /= Enumeration_Rep
(L2
) then
13632 end Enumeration_Case
;
13634 -- Any other types have the same representation for these purposes
13639 end Has_Compatible_Representation
;
13641 -------------------------------------
13642 -- Inherit_Aspects_At_Freeze_Point --
13643 -------------------------------------
13645 procedure Inherit_Aspects_At_Freeze_Point
(Typ
: Entity_Id
) is
13646 function Get_Inherited_Rep_Item
13648 Nam
: Name_Id
) return Node_Id
;
13649 -- Search the Rep_Item chain of entity E for an instance of a rep item
13650 -- (pragma, attribute definition clause, or aspect specification) whose
13651 -- name matches the given name Nam, and that has been inherited from its
13652 -- parent, i.e. that has not been directly specified for E . If one is
13653 -- found, it is returned, otherwise Empty is returned.
13655 function Get_Inherited_Rep_Item
13658 Nam2
: Name_Id
) return Node_Id
;
13659 -- Search the Rep_Item chain of entity E for an instance of a rep item
13660 -- (pragma, attribute definition clause, or aspect specification) whose
13661 -- name matches one of the given names Nam1 or Nam2, and that has been
13662 -- inherited from its parent, i.e. that has not been directly specified
13663 -- for E . If one is found, it is returned, otherwise Empty is returned.
13665 function Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
13666 (Rep_Item
: Node_Id
) return Boolean;
13667 -- This routine checks if Rep_Item is either a pragma or an aspect
13668 -- specification node whose corresponding pragma (if any) is present in
13669 -- the Rep Item chain of the entity it has been specified to.
13671 ----------------------------
13672 -- Get_Inherited_Rep_Item --
13673 ----------------------------
13675 function Get_Inherited_Rep_Item
13677 Nam
: Name_Id
) return Node_Id
13679 Rep
: constant Node_Id
13680 := Get_Rep_Item
(E
, Nam
, Check_Parents
=> True);
13683 and then not Has_Rep_Item
(E
, Nam
, Check_Parents
=> False)
13689 end Get_Inherited_Rep_Item
;
13691 function Get_Inherited_Rep_Item
13694 Nam2
: Name_Id
) return Node_Id
13696 Rep
: constant Node_Id
13697 := Get_Rep_Item
(E
, Nam1
, Nam2
, Check_Parents
=> True);
13700 and then not Has_Rep_Item
(E
, Nam1
, Nam2
, Check_Parents
=> False)
13706 end Get_Inherited_Rep_Item
;
13708 --------------------------------------------------
13709 -- Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item --
13710 --------------------------------------------------
13712 function Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
13713 (Rep_Item
: Node_Id
) return Boolean
13717 Nkind
(Rep_Item
) = N_Pragma
13719 Present_In_Rep_Item
(Entity
(Rep_Item
), Aspect_Rep_Item
(Rep_Item
));
13720 end Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
;
13724 -- Start of processing for Inherit_Aspects_At_Freeze_Point
13727 -- A representation item is either subtype-specific (Size and Alignment
13728 -- clauses) or type-related (all others). Subtype-specific aspects may
13729 -- differ for different subtypes of the same type (RM 13.1.8).
13731 -- A derived type inherits each type-related representation aspect of
13732 -- its parent type that was directly specified before the declaration of
13733 -- the derived type (RM 13.1.15).
13735 -- A derived subtype inherits each subtype-specific representation
13736 -- aspect of its parent subtype that was directly specified before the
13737 -- declaration of the derived type (RM 13.1.15).
13739 -- The general processing involves inheriting a representation aspect
13740 -- from a parent type whenever the first rep item (aspect specification,
13741 -- attribute definition clause, pragma) corresponding to the given
13742 -- representation aspect in the rep item chain of Typ, if any, isn't
13743 -- directly specified to Typ but to one of its parents.
13745 -- In addition, Convention must be propagated from base type to subtype,
13746 -- because the subtype may have been declared on an incomplete view.
13748 if Nkind
(Parent
(Typ
)) = N_Private_Extension_Declaration
then
13754 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Ada_05
, Name_Ada_2005
);
13756 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
13758 Set_Is_Ada_2005_Only
(Typ
);
13763 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Ada_12
, Name_Ada_2012
);
13765 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
13767 Set_Is_Ada_2012_Only
(Typ
);
13772 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Ada_2022
);
13774 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
13776 Set_Is_Ada_2022_Only
(Typ
);
13781 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Atomic
, Name_Shared
);
13783 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
13785 Set_Is_Atomic
(Typ
);
13786 Set_Is_Volatile
(Typ
);
13787 Set_Treat_As_Volatile
(Typ
);
13792 if Is_Record_Type
(Typ
)
13793 and then Typ
/= Base_Type
(Typ
) and then Is_Frozen
(Base_Type
(Typ
))
13795 Set_Convention
(Typ
, Convention
(Base_Type
(Typ
)));
13798 -- Default_Component_Value (for base types only)
13800 -- Note that we need to look into the first subtype because the base
13801 -- type may be the implicit base type built by the compiler for the
13802 -- declaration of a constrained subtype with the aspect.
13804 if Is_Array_Type
(Typ
) and then Is_Base_Type
(Typ
) then
13806 F_Typ
: constant Entity_Id
:= First_Subtype
(Typ
);
13812 Get_Inherited_Rep_Item
(F_Typ
, Name_Default_Component_Value
);
13813 if Present
(Rep
) then
13816 -- Deal with private types
13818 if Is_Private_Type
(E
) then
13819 E
:= Full_View
(E
);
13822 Set_Default_Aspect_Component_Value
13823 (Typ
, Default_Aspect_Component_Value
(E
));
13824 Set_Has_Default_Aspect
(Typ
);
13829 -- Default_Value (for base types only)
13831 -- Note that we need to look into the first subtype because the base
13832 -- type may be the implicit base type built by the compiler for the
13833 -- declaration of a constrained subtype with the aspect.
13835 if Is_Scalar_Type
(Typ
) and then Is_Base_Type
(Typ
) then
13837 F_Typ
: constant Entity_Id
:= First_Subtype
(Typ
);
13842 Rep
:= Get_Inherited_Rep_Item
(F_Typ
, Name_Default_Value
);
13843 if Present
(Rep
) then
13846 -- Deal with private types
13848 if Is_Private_Type
(E
) then
13849 E
:= Full_View
(E
);
13852 Set_Default_Aspect_Value
(Typ
, Default_Aspect_Value
(E
));
13853 Set_Has_Default_Aspect
(Typ
);
13860 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Discard_Names
);
13862 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
13864 Set_Discard_Names
(Typ
);
13869 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Volatile
);
13871 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
13873 Set_Is_Volatile
(Typ
);
13874 Set_Treat_As_Volatile
(Typ
);
13877 -- Volatile_Full_Access and Full_Access_Only
13879 Rep
:= Get_Inherited_Rep_Item
13880 (Typ
, Name_Volatile_Full_Access
, Name_Full_Access_Only
);
13882 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
13884 Set_Is_Volatile_Full_Access
(Typ
);
13885 Set_Is_Volatile
(Typ
);
13886 Set_Treat_As_Volatile
(Typ
);
13889 -- Inheritance for derived types only
13891 if Is_Derived_Type
(Typ
) then
13893 Bas_Typ
: constant Entity_Id
:= Base_Type
(Typ
);
13894 Imp_Bas_Typ
: constant Entity_Id
:= Implementation_Base_Type
(Typ
);
13897 -- Atomic_Components
13899 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Atomic_Components
);
13901 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
13903 Set_Has_Atomic_Components
(Imp_Bas_Typ
);
13906 -- Volatile_Components
13908 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Volatile_Components
);
13910 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
13912 Set_Has_Volatile_Components
(Imp_Bas_Typ
);
13915 -- Finalize_Storage_Only
13917 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Finalize_Storage_Only
);
13918 if Present
(Rep
) then
13919 Set_Finalize_Storage_Only
(Bas_Typ
);
13922 -- Universal_Aliasing
13924 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Universal_Aliasing
);
13926 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
13928 Set_Universal_Aliasing
(Imp_Bas_Typ
);
13933 if Is_Record_Type
(Typ
) and then Typ
= Bas_Typ
then
13934 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Bit_Order
);
13935 if Present
(Rep
) then
13936 Set_Reverse_Bit_Order
(Bas_Typ
,
13938 (Implementation_Base_Type
(Etype
(Bas_Typ
))));
13942 -- Scalar_Storage_Order
13944 if (Is_Record_Type
(Typ
) or else Is_Array_Type
(Typ
))
13945 and then Typ
= Bas_Typ
13947 -- For a type extension, always inherit from parent; otherwise
13948 -- inherit if no default applies. Note: we do not check for
13949 -- an explicit rep item on the parent type when inheriting,
13950 -- because the parent SSO may itself have been set by default.
13952 if not Has_Rep_Item
(First_Subtype
(Typ
),
13953 Name_Scalar_Storage_Order
, False)
13954 and then (Is_Tagged_Type
(Bas_Typ
)
13955 or else not (SSO_Set_Low_By_Default
(Bas_Typ
)
13957 SSO_Set_High_By_Default
(Bas_Typ
)))
13959 Set_Reverse_Storage_Order
(Bas_Typ
,
13960 Reverse_Storage_Order
13961 (Implementation_Base_Type
(Etype
(Bas_Typ
))));
13963 -- Clear default SSO indications, since the inherited aspect
13964 -- which was set explicitly overrides the default.
13966 Set_SSO_Set_Low_By_Default
(Bas_Typ
, False);
13967 Set_SSO_Set_High_By_Default
(Bas_Typ
, False);
13972 end Inherit_Aspects_At_Freeze_Point
;
13974 ---------------------------------
13975 -- Inherit_Delayed_Rep_Aspects --
13976 ---------------------------------
13978 procedure Inherit_Delayed_Rep_Aspects
(Typ
: Entity_Id
) is
13984 -- Find the first aspect that has been inherited
13986 N
:= First_Rep_Item
(Typ
);
13987 while Present
(N
) loop
13988 if Nkind
(N
) = N_Aspect_Specification
then
13989 exit when Entity
(N
) /= Typ
;
13995 -- There must be one if we reach here
13997 pragma Assert
(Present
(N
));
14000 -- Loop through delayed aspects for the parent type
14002 while Present
(N
) loop
14003 if Nkind
(N
) = N_Aspect_Specification
then
14004 exit when Entity
(N
) /= P
;
14006 if Is_Delayed_Aspect
(N
) then
14007 A
:= Get_Aspect_Id
(N
);
14009 -- Process delayed rep aspect. For Boolean attributes it is
14010 -- not possible to cancel an attribute once set (the attempt
14011 -- to use an aspect with xxx => False is an error) for a
14012 -- derived type. So for those cases, we do not have to check
14013 -- if a clause has been given for the derived type, since it
14014 -- is harmless to set it again if it is already set.
14020 when Aspect_Alignment
=>
14021 if not Has_Alignment_Clause
(Typ
) then
14022 Set_Alignment
(Typ
, Alignment
(P
));
14027 when Aspect_Atomic
=>
14028 if Is_Atomic
(P
) then
14029 Set_Is_Atomic
(Typ
);
14032 -- Atomic_Components
14034 when Aspect_Atomic_Components
=>
14035 if Has_Atomic_Components
(P
) then
14036 Set_Has_Atomic_Components
(Base_Type
(Typ
));
14041 when Aspect_Bit_Order
=>
14042 if Is_Record_Type
(Typ
)
14043 and then No
(Get_Attribute_Definition_Clause
14044 (Typ
, Attribute_Bit_Order
))
14045 and then Reverse_Bit_Order
(P
)
14047 Set_Reverse_Bit_Order
(Base_Type
(Typ
));
14052 when Aspect_Component_Size
=>
14053 if Is_Array_Type
(Typ
)
14054 and then not Has_Component_Size_Clause
(Typ
)
14057 (Base_Type
(Typ
), Component_Size
(P
));
14062 when Aspect_Machine_Radix
=>
14063 if Is_Decimal_Fixed_Point_Type
(Typ
)
14064 and then not Has_Machine_Radix_Clause
(Typ
)
14066 Set_Machine_Radix_10
(Typ
, Machine_Radix_10
(P
));
14069 -- Object_Size (also Size which also sets Object_Size)
14071 when Aspect_Object_Size
14074 if not Has_Size_Clause
(Typ
)
14076 No
(Get_Attribute_Definition_Clause
14077 (Typ
, Attribute_Object_Size
))
14079 Set_Esize
(Typ
, Esize
(P
));
14084 when Aspect_Pack
=>
14085 if not Is_Packed
(Typ
) then
14086 Set_Is_Packed
(Base_Type
(Typ
));
14088 if Is_Bit_Packed_Array
(P
) then
14089 Set_Is_Bit_Packed_Array
(Base_Type
(Typ
));
14090 Set_Packed_Array_Impl_Type
14091 (Typ
, Packed_Array_Impl_Type
(P
));
14095 -- Scalar_Storage_Order
14097 when Aspect_Scalar_Storage_Order
=>
14098 if (Is_Record_Type
(Typ
) or else Is_Array_Type
(Typ
))
14099 and then No
(Get_Attribute_Definition_Clause
14100 (Typ
, Attribute_Scalar_Storage_Order
))
14101 and then Reverse_Storage_Order
(P
)
14103 Set_Reverse_Storage_Order
(Base_Type
(Typ
));
14105 -- Clear default SSO indications, since the aspect
14106 -- overrides the default.
14108 Set_SSO_Set_Low_By_Default
(Base_Type
(Typ
), False);
14109 Set_SSO_Set_High_By_Default
(Base_Type
(Typ
), False);
14114 when Aspect_Small
=>
14115 if Is_Fixed_Point_Type
(Typ
)
14116 and then not Has_Small_Clause
(Typ
)
14118 Set_Small_Value
(Typ
, Small_Value
(P
));
14123 when Aspect_Storage_Size
=>
14124 if (Is_Access_Type
(Typ
) or else Is_Task_Type
(Typ
))
14125 and then not Has_Storage_Size_Clause
(Typ
)
14127 Set_Storage_Size_Variable
14128 (Base_Type
(Typ
), Storage_Size_Variable
(P
));
14133 when Aspect_Value_Size
=>
14135 -- Value_Size is never inherited, it is either set by
14136 -- default, or it is explicitly set for the derived
14137 -- type. So nothing to do here.
14143 when Aspect_Volatile
=>
14144 if Is_Volatile
(P
) then
14145 Set_Is_Volatile
(Typ
);
14148 -- Volatile_Full_Access (also Full_Access_Only)
14150 when Aspect_Volatile_Full_Access
14151 | Aspect_Full_Access_Only
14153 if Is_Volatile_Full_Access
(P
) then
14154 Set_Is_Volatile_Full_Access
(Typ
);
14157 -- Volatile_Components
14159 when Aspect_Volatile_Components
=>
14160 if Has_Volatile_Components
(P
) then
14161 Set_Has_Volatile_Components
(Base_Type
(Typ
));
14164 -- That should be all the Rep Aspects
14167 pragma Assert
(Aspect_Delay
(A
) /= Rep_Aspect
);
14175 end Inherit_Delayed_Rep_Aspects
;
14181 procedure Initialize
is
14183 Address_Clause_Checks
.Init
;
14184 Unchecked_Conversions
.Init
;
14186 -- The following might be needed in the future for some non-GCC back
14188 -- if AAMP_On_Target then
14189 -- Independence_Checks.Init;
14193 ---------------------------
14194 -- Install_Discriminants --
14195 ---------------------------
14197 procedure Install_Discriminants
(E
: Entity_Id
) is
14201 Disc
:= First_Discriminant
(E
);
14202 while Present
(Disc
) loop
14203 Prev
:= Current_Entity
(Disc
);
14204 Set_Current_Entity
(Disc
);
14205 Set_Is_Immediately_Visible
(Disc
);
14206 Set_Homonym
(Disc
, Prev
);
14207 Next_Discriminant
(Disc
);
14209 end Install_Discriminants
;
14211 -------------------------
14212 -- Is_Operational_Item --
14213 -------------------------
14215 function Is_Operational_Item
(N
: Node_Id
) return Boolean is
14217 -- List of operational items is given in AARM 13.1(8.mm/1). It is
14218 -- clearly incomplete, as it does not include iterator aspects, among
14221 return Nkind
(N
) = N_Attribute_Definition_Clause
14223 Get_Attribute_Id
(Chars
(N
)) in Attribute_Constant_Indexing
14224 | Attribute_External_Tag
14225 | Attribute_Default_Iterator
14226 | Attribute_Implicit_Dereference
14228 | Attribute_Iterable
14229 | Attribute_Iterator_Element
14231 | Attribute_Put_Image
14233 | Attribute_Variable_Indexing
14235 end Is_Operational_Item
;
14237 -------------------------
14238 -- Is_Predicate_Static --
14239 -------------------------
14241 -- Note: the basic legality of the expression has already been checked, so
14242 -- we don't need to worry about cases or ranges on strings for example.
14244 function Is_Predicate_Static
14247 Warn
: Boolean := True) return Boolean
14249 function All_Static_Case_Alternatives
(L
: List_Id
) return Boolean;
14250 -- Given a list of case expression alternatives, returns True if all
14251 -- the alternatives are static (have all static choices, and a static
14254 function Is_Type_Ref
(N
: Node_Id
) return Boolean;
14255 pragma Inline
(Is_Type_Ref
);
14256 -- Returns True if N is a reference to the type for the predicate in the
14257 -- expression (i.e. if it is an identifier whose Chars field matches the
14258 -- Nam given in the call). N must not be parenthesized, if the type name
14259 -- appears in parens, this routine will return False.
14261 -- The routine also returns True for function calls generated during the
14262 -- expansion of comparison operators on strings, which are intended to
14263 -- be legal in static predicates, and are converted into calls to array
14264 -- comparison routines in the body of the corresponding predicate
14267 ----------------------------------
14268 -- All_Static_Case_Alternatives --
14269 ----------------------------------
14271 function All_Static_Case_Alternatives
(L
: List_Id
) return Boolean is
14276 while Present
(N
) loop
14277 if not (All_Static_Choices
(Discrete_Choices
(N
))
14278 and then Is_OK_Static_Expression
(Expression
(N
)))
14287 end All_Static_Case_Alternatives
;
14293 function Is_Type_Ref
(N
: Node_Id
) return Boolean is
14295 return (Nkind
(N
) = N_Identifier
14296 and then Chars
(N
) = Nam
14297 and then Paren_Count
(N
) = 0);
14300 -- helper function for recursive calls
14301 function Is_Predicate_Static_Aux
(Expr
: Node_Id
) return Boolean is
14302 (Is_Predicate_Static
(Expr
, Nam
, Warn
=> False));
14304 -- Start of processing for Is_Predicate_Static
14307 -- Handle cases like
14308 -- subtype S is Integer with Static_Predicate =>
14309 -- (Some_Integer_Variable in Integer) and then (S /= 0);
14310 -- where the predicate (which should be rejected) might have been
14311 -- transformed into just "(S /= 0)", which would appear to be
14312 -- a predicate-static expression (and therefore legal).
14314 if Is_Rewrite_Substitution
(Expr
) then
14316 -- Emit warnings for predicates that are always True or always False
14317 -- and were not originally expressed as Boolean literals.
14319 return Result
: constant Boolean :=
14320 Is_Predicate_Static_Aux
(Original_Node
(Expr
))
14322 if Result
and then Warn
and then Is_Entity_Name
(Expr
) then
14323 if Entity
(Expr
) = Standard_True
then
14324 Error_Msg_N
("predicate is redundant (always True)?", Expr
);
14325 elsif Entity
(Expr
) = Standard_False
then
14327 ("predicate is unsatisfiable (always False)?", Expr
);
14333 -- Predicate_Static means one of the following holds. Numbers are the
14334 -- corresponding paragraph numbers in (RM 3.2.4(16-22)).
14336 -- 16: A static expression
14338 if Is_OK_Static_Expression
(Expr
) then
14341 -- 17: A membership test whose simple_expression is the current
14342 -- instance, and whose membership_choice_list meets the requirements
14343 -- for a static membership test.
14345 elsif Nkind
(Expr
) in N_Membership_Test
14346 and then Is_Type_Ref
(Left_Opnd
(Expr
))
14347 and then All_Membership_Choices_Static
(Expr
)
14351 -- 18. A case_expression whose selecting_expression is the current
14352 -- instance, and whose dependent expressions are static expressions.
14354 elsif Nkind
(Expr
) = N_Case_Expression
14355 and then Is_Type_Ref
(Expression
(Expr
))
14356 and then All_Static_Case_Alternatives
(Alternatives
(Expr
))
14360 -- 19. A call to a predefined equality or ordering operator, where one
14361 -- operand is the current instance, and the other is a static
14364 -- Note: the RM is clearly wrong here in not excluding string types.
14365 -- Without this exclusion, we would allow expressions like X > "ABC"
14366 -- to be considered as predicate-static, which is clearly not intended,
14367 -- since the idea is for predicate-static to be a subset of normal
14368 -- static expressions (and "DEF" > "ABC" is not a static expression).
14370 -- However, we do allow internally generated (not from source) equality
14371 -- and inequality operations to be valid on strings (this helps deal
14372 -- with cases where we transform A in "ABC" to A = "ABC).
14374 -- In fact, it appears that the intent of the ARG is to extend static
14375 -- predicates to strings, and that the extension should probably apply
14376 -- to static expressions themselves. The code below accepts comparison
14377 -- operators that apply to static strings.
14379 elsif Nkind
(Expr
) in N_Op_Compare
14380 and then ((Is_Type_Ref
(Left_Opnd
(Expr
))
14381 and then Is_OK_Static_Expression
(Right_Opnd
(Expr
)))
14383 (Is_Type_Ref
(Right_Opnd
(Expr
))
14384 and then Is_OK_Static_Expression
(Left_Opnd
(Expr
))))
14388 -- 20. A call to a predefined boolean logical operator, where each
14389 -- operand is predicate-static.
14391 elsif (Nkind
(Expr
) in N_Op_And | N_Op_Or | N_Op_Xor
14392 and then Is_Predicate_Static_Aux
(Left_Opnd
(Expr
))
14393 and then Is_Predicate_Static_Aux
(Right_Opnd
(Expr
)))
14395 (Nkind
(Expr
) = N_Op_Not
14396 and then Is_Predicate_Static_Aux
(Right_Opnd
(Expr
)))
14400 -- 21. A short-circuit control form where both operands are
14401 -- predicate-static.
14403 elsif Nkind
(Expr
) in N_Short_Circuit
14404 and then Is_Predicate_Static_Aux
(Left_Opnd
(Expr
))
14405 and then Is_Predicate_Static_Aux
(Right_Opnd
(Expr
))
14409 -- 22. A parenthesized predicate-static expression. This does not
14410 -- require any special test, since we just ignore paren levels in
14411 -- all the cases above.
14413 -- One more test that is an implementation artifact caused by the fact
14414 -- that we are analyzing not the original expression, but the generated
14415 -- expression in the body of the predicate function. This can include
14416 -- references to inherited predicates, so that the expression we are
14417 -- processing looks like:
14419 -- xxPredicate (typ (Inns)) and then expression
14421 -- Where the call is to a Predicate function for an inherited predicate.
14422 -- We simply ignore such a call, which could be to either a dynamic or
14423 -- a static predicate. Note that if the parent predicate is dynamic then
14424 -- eventually this type will be marked as dynamic, but you are allowed
14425 -- to specify a static predicate for a subtype which is inheriting a
14426 -- dynamic predicate, so the static predicate validation here ignores
14427 -- the inherited predicate even if it is dynamic.
14428 -- In all cases, a static predicate can only apply to a scalar type.
14430 elsif Nkind
(Expr
) = N_Function_Call
14431 and then Is_Predicate_Function
(Entity
(Name
(Expr
)))
14432 and then Is_Scalar_Type
(Etype
(First_Entity
(Entity
(Name
(Expr
)))))
14436 -- That's an exhaustive list of tests, all other cases are not
14437 -- predicate-static, so we return False.
14442 end Is_Predicate_Static
;
14444 ----------------------
14445 -- Is_Static_Choice --
14446 ----------------------
14448 function Is_Static_Choice
(N
: Node_Id
) return Boolean is
14450 return Nkind
(N
) = N_Others_Choice
14451 or else Is_OK_Static_Expression
(N
)
14452 or else (Is_Entity_Name
(N
) and then Is_Type
(Entity
(N
))
14453 and then Is_OK_Static_Subtype
(Entity
(N
)))
14454 or else (Nkind
(N
) = N_Subtype_Indication
14455 and then Is_OK_Static_Subtype
(Entity
(N
)))
14456 or else (Nkind
(N
) = N_Range
and then Is_OK_Static_Range
(N
));
14457 end Is_Static_Choice
;
14459 ------------------------------
14460 -- Is_Type_Related_Rep_Item --
14461 ------------------------------
14463 function Is_Type_Related_Rep_Item
(N
: Node_Id
) return Boolean is
14466 when N_Attribute_Definition_Clause
=>
14467 -- See AARM 13.1(8.f-8.x) list items that end in "clause"
14468 -- ???: include any GNAT-defined attributes here?
14469 return Get_Attribute_Id
(Chars
(N
)) in Attribute_Bit_Order
14470 | Attribute_Component_Size
14471 | Attribute_Machine_Radix
14472 | Attribute_Storage_Pool
14473 | Attribute_Stream_Size
;
14476 case Get_Pragma_Id
(N
) is
14477 -- See AARM 13.1(8.f-8.x) list items that start with "pragma"
14478 -- ???: include any GNAT-defined pragmas here?
14482 | Pragma_Convention
14484 | Pragma_Independent
14486 | Pragma_Atomic_Components
14487 | Pragma_Independent_Components
14488 | Pragma_Volatile_Components
14489 | Pragma_Discard_Names
14496 when N_Enumeration_Representation_Clause
14497 | N_Record_Representation_Clause
14506 end Is_Type_Related_Rep_Item
;
14508 ---------------------
14509 -- Kill_Rep_Clause --
14510 ---------------------
14512 procedure Kill_Rep_Clause
(N
: Node_Id
) is
14514 pragma Assert
(Ignore_Rep_Clauses
);
14516 -- Note: we use Replace rather than Rewrite, because we don't want
14517 -- tools to be able to use Original_Node to dig out the (undecorated)
14518 -- rep clause that is being replaced.
14520 Replace
(N
, Make_Null_Statement
(Sloc
(N
)));
14522 -- The null statement must be marked as not coming from source. This is
14523 -- so that tools ignore it, and also the back end does not expect bogus
14524 -- "from source" null statements in weird places (e.g. in declarative
14525 -- regions where such null statements are not allowed).
14527 Set_Comes_From_Source
(N
, False);
14528 end Kill_Rep_Clause
;
14534 function Minimum_Size
14536 Biased
: Boolean := False) return Int
14538 Lo
: Uint
:= No_Uint
;
14539 Hi
: Uint
:= No_Uint
;
14540 LoR
: Ureal
:= No_Ureal
;
14541 HiR
: Ureal
:= No_Ureal
;
14542 LoSet
: Boolean := False;
14543 HiSet
: Boolean := False;
14546 Ancest
: Entity_Id
;
14547 R_Typ
: constant Entity_Id
:= Root_Type
(T
);
14552 if T
= Any_Type
then
14553 return Unknown_Minimum_Size
;
14555 -- For generic types, just return unknown. There cannot be any
14556 -- legitimate need to know such a size, but this routine may be
14557 -- called with a generic type as part of normal processing.
14559 elsif Is_Generic_Type
(R_Typ
) or else R_Typ
= Any_Type
then
14560 return Unknown_Minimum_Size
;
14562 -- Access types (cannot have size smaller than System.Address)
14564 elsif Is_Access_Type
(T
) then
14565 return System_Address_Size
;
14567 -- Floating-point types
14569 elsif Is_Floating_Point_Type
(T
) then
14570 return UI_To_Int
(Esize
(R_Typ
));
14574 elsif Is_Discrete_Type
(T
) then
14576 -- The following loop is looking for the nearest compile time known
14577 -- bounds following the ancestor subtype chain. The idea is to find
14578 -- the most restrictive known bounds information.
14582 if Ancest
= Any_Type
or else Etype
(Ancest
) = Any_Type
then
14583 return Unknown_Minimum_Size
;
14587 if Compile_Time_Known_Value
(Type_Low_Bound
(Ancest
)) then
14588 Lo
:= Expr_Rep_Value
(Type_Low_Bound
(Ancest
));
14595 if Compile_Time_Known_Value
(Type_High_Bound
(Ancest
)) then
14596 Hi
:= Expr_Rep_Value
(Type_High_Bound
(Ancest
));
14602 Ancest
:= Ancestor_Subtype
(Ancest
);
14604 if No
(Ancest
) then
14605 Ancest
:= Base_Type
(T
);
14607 if Is_Generic_Type
(Ancest
) then
14608 return Unknown_Minimum_Size
;
14613 -- Fixed-point types. We can't simply use Expr_Value to get the
14614 -- Corresponding_Integer_Value values of the bounds, since these do not
14615 -- get set till the type is frozen, and this routine can be called
14616 -- before the type is frozen. Similarly the test for bounds being static
14617 -- needs to include the case where we have unanalyzed real literals for
14618 -- the same reason.
14620 elsif Is_Fixed_Point_Type
(T
) then
14622 -- The following loop is looking for the nearest compile time known
14623 -- bounds following the ancestor subtype chain. The idea is to find
14624 -- the most restrictive known bounds information.
14628 if Ancest
= Any_Type
or else Etype
(Ancest
) = Any_Type
then
14629 return Unknown_Minimum_Size
;
14632 -- Note: In the following two tests for LoSet and HiSet, it may
14633 -- seem redundant to test for N_Real_Literal here since normally
14634 -- one would assume that the test for the value being known at
14635 -- compile time includes this case. However, there is a glitch.
14636 -- If the real literal comes from folding a non-static expression,
14637 -- then we don't consider any non- static expression to be known
14638 -- at compile time if we are in configurable run time mode (needed
14639 -- in some cases to give a clearer definition of what is and what
14640 -- is not accepted). So the test is indeed needed. Without it, we
14641 -- would set neither Lo_Set nor Hi_Set and get an infinite loop.
14644 if Nkind
(Type_Low_Bound
(Ancest
)) = N_Real_Literal
14645 or else Compile_Time_Known_Value
(Type_Low_Bound
(Ancest
))
14647 LoR
:= Expr_Value_R
(Type_Low_Bound
(Ancest
));
14654 if Nkind
(Type_High_Bound
(Ancest
)) = N_Real_Literal
14655 or else Compile_Time_Known_Value
(Type_High_Bound
(Ancest
))
14657 HiR
:= Expr_Value_R
(Type_High_Bound
(Ancest
));
14663 Ancest
:= Ancestor_Subtype
(Ancest
);
14665 if No
(Ancest
) then
14666 Ancest
:= Base_Type
(T
);
14668 if Is_Generic_Type
(Ancest
) then
14669 return Unknown_Minimum_Size
;
14674 Lo
:= UR_To_Uint
(LoR
/ Small_Value
(T
));
14675 Hi
:= UR_To_Uint
(HiR
/ Small_Value
(T
));
14677 -- No other types allowed
14680 raise Program_Error
;
14683 -- Fall through with Hi and Lo set. Deal with biased case
14686 and then not Is_Fixed_Point_Type
(T
)
14687 and then not (Is_Enumeration_Type
(T
)
14688 and then Has_Non_Standard_Rep
(T
)))
14689 or else Has_Biased_Representation
(T
)
14695 -- Null range case, size is always zero. We only do this in the discrete
14696 -- type case, since that's the odd case that came up. Probably we should
14697 -- also do this in the fixed-point case, but doing so causes peculiar
14698 -- gigi failures, and it is not worth worrying about this incredibly
14699 -- marginal case (explicit null-range fixed-point type declarations).
14701 if Lo
> Hi
and then Is_Discrete_Type
(T
) then
14704 -- Signed case. Note that we consider types like range 1 .. -1 to be
14705 -- signed for the purpose of computing the size, since the bounds have
14706 -- to be accommodated in the base type.
14708 elsif Lo
< 0 or else Hi
< 0 then
14712 -- S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
14713 -- Note that we accommodate the case where the bounds cross. This
14714 -- can happen either because of the way the bounds are declared
14715 -- or because of the algorithm in Freeze_Fixed_Point_Type.
14729 -- If both bounds are positive, make sure that both are represen-
14730 -- table in the case where the bounds are crossed. This can happen
14731 -- either because of the way the bounds are declared, or because of
14732 -- the algorithm in Freeze_Fixed_Point_Type.
14738 -- S = size, (can accommodate 0 .. (2**size - 1))
14741 while Hi
>= Uint_2
** S
loop
14749 ------------------------------
14750 -- New_Put_Image_Subprogram --
14751 ------------------------------
14753 procedure New_Put_Image_Subprogram
14758 Loc
: constant Source_Ptr
:= Sloc
(N
);
14759 Sname
: constant Name_Id
:=
14760 Make_TSS_Name
(Base_Type
(Ent
), TSS_Put_Image
);
14761 Subp_Id
: Entity_Id
;
14762 Subp_Decl
: Node_Id
;
14766 Defer_Declaration
: constant Boolean :=
14767 Is_Tagged_Type
(Ent
) or else Is_Private_Type
(Ent
);
14768 -- For a tagged type, there is a declaration at the freeze point, and
14769 -- we must generate only a completion of this declaration. We do the
14770 -- same for private types, because the full view might be tagged.
14771 -- Otherwise we generate a declaration at the point of the attribute
14772 -- definition clause. If the attribute definition comes from an aspect
14773 -- specification the declaration is part of the freeze actions of the
14776 function Build_Spec
return Node_Id
;
14777 -- Used for declaration and renaming declaration, so that this is
14778 -- treated as a renaming_as_body.
14784 function Build_Spec
return Node_Id
is
14787 T_Ref
: constant Node_Id
:= New_Occurrence_Of
(Etyp
, Loc
);
14790 Subp_Id
:= Make_Defining_Identifier
(Loc
, Sname
);
14792 -- S : Root_Buffer_Type'Class
14794 Formals
:= New_List
(
14795 Make_Parameter_Specification
(Loc
,
14796 Defining_Identifier
=>
14797 Make_Defining_Identifier
(Loc
, Name_S
),
14798 In_Present
=> True,
14799 Out_Present
=> True,
14801 New_Occurrence_Of
(Etype
(F
), Loc
)));
14805 Append_To
(Formals
,
14806 Make_Parameter_Specification
(Loc
,
14807 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_V
),
14808 Parameter_Type
=> T_Ref
));
14811 Make_Procedure_Specification
(Loc
,
14812 Defining_Unit_Name
=> Subp_Id
,
14813 Parameter_Specifications
=> Formals
);
14818 -- Start of processing for New_Put_Image_Subprogram
14821 F
:= First_Formal
(Subp
);
14823 Etyp
:= Etype
(Next_Formal
(F
));
14825 -- Prepare subprogram declaration and insert it as an action on the
14826 -- clause node. The visibility for this entity is used to test for
14827 -- visibility of the attribute definition clause (in the sense of
14828 -- 8.3(23) as amended by AI-195).
14830 if not Defer_Declaration
then
14832 Make_Subprogram_Declaration
(Loc
,
14833 Specification
=> Build_Spec
);
14835 -- For a tagged type, there is always a visible declaration for the
14836 -- Put_Image TSS (it is a predefined primitive operation), and the
14837 -- completion of this declaration occurs at the freeze point, which is
14838 -- not always visible at places where the attribute definition clause is
14839 -- visible. So, we create a dummy entity here for the purpose of
14840 -- tracking the visibility of the attribute definition clause itself.
14844 Make_Defining_Identifier
(Loc
, New_External_Name
(Sname
, 'V'));
14846 Make_Object_Declaration
(Loc
,
14847 Defining_Identifier
=> Subp_Id
,
14848 Object_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
));
14851 if not Defer_Declaration
14852 and then From_Aspect_Specification
(N
)
14853 and then Has_Delayed_Freeze
(Ent
)
14855 Append_Freeze_Action
(Ent
, Subp_Decl
);
14858 Insert_Action
(N
, Subp_Decl
);
14859 Set_Entity
(N
, Subp_Id
);
14863 Make_Subprogram_Renaming_Declaration
(Loc
,
14864 Specification
=> Build_Spec
,
14865 Name
=> New_Occurrence_Of
(Subp
, Loc
));
14867 if Defer_Declaration
then
14868 Set_TSS
(Base_Type
(Ent
), Subp_Id
);
14871 if From_Aspect_Specification
(N
) then
14872 Append_Freeze_Action
(Ent
, Subp_Decl
);
14874 Insert_Action
(N
, Subp_Decl
);
14877 Copy_TSS
(Subp_Id
, Base_Type
(Ent
));
14879 end New_Put_Image_Subprogram
;
14881 ---------------------------
14882 -- New_Stream_Subprogram --
14883 ---------------------------
14885 procedure New_Stream_Subprogram
14889 Nam
: TSS_Name_Type
)
14891 Loc
: constant Source_Ptr
:= Sloc
(N
);
14892 Sname
: constant Name_Id
:= Make_TSS_Name
(Base_Type
(Ent
), Nam
);
14893 Subp_Id
: Entity_Id
;
14894 Subp_Decl
: Node_Id
;
14898 Defer_Declaration
: constant Boolean :=
14899 Is_Tagged_Type
(Ent
) or else Is_Private_Type
(Ent
);
14900 -- For a tagged type, there is a declaration for each stream attribute
14901 -- at the freeze point, and we must generate only a completion of this
14902 -- declaration. We do the same for private types, because the full view
14903 -- might be tagged. Otherwise we generate a declaration at the point of
14904 -- the attribute definition clause. If the attribute definition comes
14905 -- from an aspect specification the declaration is part of the freeze
14906 -- actions of the type.
14908 function Build_Spec
return Node_Id
;
14909 -- Used for declaration and renaming declaration, so that this is
14910 -- treated as a renaming_as_body.
14916 function Build_Spec
return Node_Id
is
14917 Out_P
: constant Boolean := (Nam
= TSS_Stream_Read
);
14920 T_Ref
: constant Node_Id
:= New_Occurrence_Of
(Etyp
, Loc
);
14923 Subp_Id
:= Make_Defining_Identifier
(Loc
, Sname
);
14925 -- S : access Root_Stream_Type'Class
14927 Formals
:= New_List
(
14928 Make_Parameter_Specification
(Loc
,
14929 Defining_Identifier
=>
14930 Make_Defining_Identifier
(Loc
, Name_S
),
14932 Make_Access_Definition
(Loc
,
14934 New_Occurrence_Of
(
14935 Designated_Type
(Etype
(F
)), Loc
))));
14937 if Nam
= TSS_Stream_Input
then
14939 Make_Function_Specification
(Loc
,
14940 Defining_Unit_Name
=> Subp_Id
,
14941 Parameter_Specifications
=> Formals
,
14942 Result_Definition
=> T_Ref
);
14946 Append_To
(Formals
,
14947 Make_Parameter_Specification
(Loc
,
14948 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_V
),
14949 Out_Present
=> Out_P
,
14950 Parameter_Type
=> T_Ref
));
14953 Make_Procedure_Specification
(Loc
,
14954 Defining_Unit_Name
=> Subp_Id
,
14955 Parameter_Specifications
=> Formals
);
14961 -- Start of processing for New_Stream_Subprogram
14964 F
:= First_Formal
(Subp
);
14966 if Ekind
(Subp
) = E_Procedure
then
14967 Etyp
:= Etype
(Next_Formal
(F
));
14969 Etyp
:= Etype
(Subp
);
14972 -- Prepare subprogram declaration and insert it as an action on the
14973 -- clause node. The visibility for this entity is used to test for
14974 -- visibility of the attribute definition clause (in the sense of
14975 -- 8.3(23) as amended by AI-195).
14977 if not Defer_Declaration
then
14979 Make_Subprogram_Declaration
(Loc
,
14980 Specification
=> Build_Spec
);
14982 -- For a tagged type, there is always a visible declaration for each
14983 -- stream TSS (it is a predefined primitive operation), and the
14984 -- completion of this declaration occurs at the freeze point, which is
14985 -- not always visible at places where the attribute definition clause is
14986 -- visible. So, we create a dummy entity here for the purpose of
14987 -- tracking the visibility of the attribute definition clause itself.
14991 Make_Defining_Identifier
(Loc
, New_External_Name
(Sname
, 'V'));
14993 Make_Object_Declaration
(Loc
,
14994 Defining_Identifier
=> Subp_Id
,
14995 Object_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
));
14998 if not Defer_Declaration
14999 and then From_Aspect_Specification
(N
)
15000 and then Has_Delayed_Freeze
(Ent
)
15002 Append_Freeze_Action
(Ent
, Subp_Decl
);
15005 Insert_Action
(N
, Subp_Decl
);
15006 Set_Entity
(N
, Subp_Id
);
15010 Make_Subprogram_Renaming_Declaration
(Loc
,
15011 Specification
=> Build_Spec
,
15012 Name
=> New_Occurrence_Of
(Subp
, Loc
));
15014 if Defer_Declaration
then
15015 Set_TSS
(Base_Type
(Ent
), Subp_Id
);
15018 if From_Aspect_Specification
(N
) then
15019 Append_Freeze_Action
(Ent
, Subp_Decl
);
15021 Insert_Action
(N
, Subp_Decl
);
15024 Copy_TSS
(Subp_Id
, Base_Type
(Ent
));
15026 end New_Stream_Subprogram
;
15028 ----------------------
15029 -- No_Type_Rep_Item --
15030 ----------------------
15032 procedure No_Type_Rep_Item
(N
: Node_Id
) is
15034 Error_Msg_N
("|type-related representation item not permitted!", N
);
15035 end No_Type_Rep_Item
;
15041 procedure Pop_Type
(E
: Entity_Id
) is
15043 if Ekind
(E
) = E_Record_Type
and then E
= Current_Scope
then
15047 and then Has_Discriminants
(E
)
15048 and then Nkind
(Parent
(E
)) /= N_Subtype_Declaration
15050 Uninstall_Discriminants
(E
);
15059 procedure Push_Type
(E
: Entity_Id
) is
15063 if Ekind
(E
) = E_Record_Type
then
15066 Comp
:= First_Component
(E
);
15067 while Present
(Comp
) loop
15068 Install_Entity
(Comp
);
15069 Next_Component
(Comp
);
15072 if Has_Discriminants
(E
) then
15073 Install_Discriminants
(E
);
15077 and then Has_Discriminants
(E
)
15078 and then Nkind
(Parent
(E
)) /= N_Subtype_Declaration
15081 Install_Discriminants
(E
);
15085 -----------------------------------
15086 -- Register_Address_Clause_Check --
15087 -----------------------------------
15089 procedure Register_Address_Clause_Check
15096 ACS
: constant Boolean := Scope_Suppress
.Suppress
(Alignment_Check
);
15098 Address_Clause_Checks
.Append
((N
, X
, A
, Y
, Off
, ACS
));
15099 end Register_Address_Clause_Check
;
15101 ------------------------
15102 -- Rep_Item_Too_Early --
15103 ------------------------
15105 function Rep_Item_Too_Early
(T
: Entity_Id
; N
: Node_Id
) return Boolean is
15106 function Has_Generic_Parent
(E
: Entity_Id
) return Boolean;
15107 -- Return True if R or any ancestor is a generic type
15109 ------------------------
15110 -- Has_Generic_Parent --
15111 ------------------------
15113 function Has_Generic_Parent
(E
: Entity_Id
) return Boolean is
15114 Ancestor_Type
: Entity_Id
:= Etype
(E
);
15117 if Is_Generic_Type
(E
) then
15121 while Present
(Ancestor_Type
)
15122 and then not Is_Generic_Type
(Ancestor_Type
)
15123 and then Etype
(Ancestor_Type
) /= Ancestor_Type
15125 Ancestor_Type
:= Etype
(Ancestor_Type
);
15129 Present
(Ancestor_Type
) and then Is_Generic_Type
(Ancestor_Type
);
15130 end Has_Generic_Parent
;
15132 -- Start of processing for Rep_Item_Too_Early
15135 -- Cannot apply non-operational rep items to generic types
15137 if Is_Operational_Item
(N
) then
15141 and then Has_Generic_Parent
(T
)
15142 and then (Nkind
(N
) /= N_Pragma
15143 or else Get_Pragma_Id
(N
) /= Pragma_Convention
)
15145 if Ada_Version
< Ada_2022
then
15147 ("representation item not allowed for generic type", N
);
15154 -- Otherwise check for incomplete type
15156 if Is_Incomplete_Or_Private_Type
(T
)
15157 and then No
(Underlying_Type
(T
))
15159 (Nkind
(N
) /= N_Pragma
15160 or else Get_Pragma_Id
(N
) /= Pragma_Import
)
15163 ("representation item must be after full type declaration", N
);
15166 -- If the type has incomplete components, a representation clause is
15167 -- illegal but stream attributes and Convention pragmas are correct.
15169 elsif Has_Private_Component
(T
) then
15170 if Nkind
(N
) = N_Pragma
then
15175 ("representation item must appear after type is fully defined",
15182 end Rep_Item_Too_Early
;
15184 -----------------------
15185 -- Rep_Item_Too_Late --
15186 -----------------------
15188 function Rep_Item_Too_Late
15191 FOnly
: Boolean := False) return Boolean
15193 procedure Too_Late
;
15194 -- Output message for an aspect being specified too late
15196 -- Note that neither of the above errors is considered a serious one,
15197 -- since the effect is simply that we ignore the representation clause
15199 -- Is this really true? In any case if we make this change we must
15200 -- document the requirement in the spec of Rep_Item_Too_Late that
15201 -- if True is returned, then the rep item must be completely ignored???
15207 procedure Too_Late
is
15209 -- Other compilers seem more relaxed about rep items appearing too
15210 -- late. Since analysis tools typically don't care about rep items
15211 -- anyway, no reason to be too strict about this.
15213 if not Relaxed_RM_Semantics
then
15214 Error_Msg_N
("|representation item appears too late!", N
);
15220 Parent_Type
: Entity_Id
;
15223 -- Start of processing for Rep_Item_Too_Late
15226 -- First make sure entity is not frozen (RM 13.1(9))
15230 -- Exclude imported types, which may be frozen if they appear in a
15231 -- representation clause for a local type.
15233 and then not From_Limited_With
(T
)
15235 -- Exclude generated entities (not coming from source). The common
15236 -- case is when we generate a renaming which prematurely freezes the
15237 -- renamed internal entity, but we still want to be able to set copies
15238 -- of attribute values such as Size/Alignment.
15240 and then Comes_From_Source
(T
)
15242 -- A self-referential aspect is illegal if it forces freezing the
15243 -- entity before the corresponding pragma has been analyzed.
15245 if Nkind
(N
) in N_Attribute_Definition_Clause | N_Pragma
15246 and then From_Aspect_Specification
(N
)
15249 ("aspect specification causes premature freezing of&", N
, T
);
15250 Set_Has_Delayed_Freeze
(T
, False);
15255 S
:= First_Subtype
(T
);
15257 if Present
(Freeze_Node
(S
)) then
15258 if not Relaxed_RM_Semantics
then
15260 ("??no more representation items for }", Freeze_Node
(S
), S
);
15266 -- Check for case of untagged derived type whose parent either has
15267 -- primitive operations (pre Ada 2022), or is a by-reference type (RM
15268 -- 13.1(10)). In this case we do not output a Too_Late message, since
15269 -- there is no earlier point where the rep item could be placed to make
15271 -- ??? Confirming representation clauses should be allowed here.
15275 and then Is_Derived_Type
(T
)
15276 and then not Is_Tagged_Type
(T
)
15278 Parent_Type
:= Etype
(Base_Type
(T
));
15280 if Relaxed_RM_Semantics
then
15283 elsif Ada_Version
<= Ada_2012
15284 and then Has_Primitive_Operations
(Parent_Type
)
15287 ("|representation item not permitted before Ada 2022!", N
);
15289 ("\parent type & has primitive operations!", N
, Parent_Type
);
15292 elsif Is_By_Reference_Type
(Parent_Type
) then
15293 No_Type_Rep_Item
(N
);
15295 ("\parent type & is a by-reference type!", N
, Parent_Type
);
15300 -- No error, but one more warning to consider. The RM (surprisingly)
15301 -- allows this pattern in some cases:
15304 -- primitive operations for S
15305 -- type R is new S;
15306 -- rep clause for S
15308 -- Meaning that calls on the primitive operations of S for values of
15309 -- type R may require possibly expensive implicit conversion operations.
15310 -- So even when this is not an error, it is still worth a warning.
15312 if not Relaxed_RM_Semantics
and then Is_Type
(T
) then
15314 DTL
: constant Entity_Id
:= Derived_Type_Link
(Base_Type
(T
));
15319 -- For now, do not generate this warning for the case of
15320 -- aspect specification using Ada 2012 syntax, since we get
15321 -- wrong messages we do not understand. The whole business
15322 -- of derived types and rep items seems a bit confused when
15323 -- aspects are used, since the aspects are not evaluated
15324 -- till freeze time. However, AI12-0109 confirms (in an AARM
15325 -- ramification) that inheritance in this case is required
15328 and then not From_Aspect_Specification
(N
)
15330 if Is_By_Reference_Type
(T
)
15331 and then not Is_Tagged_Type
(T
)
15332 and then Is_Type_Related_Rep_Item
(N
)
15333 and then (Ada_Version
>= Ada_2012
15334 or else Has_Primitive_Operations
(Base_Type
(T
)))
15336 -- Treat as hard error (AI12-0109, binding interpretation).
15337 -- Implementing a change of representation is not really
15338 -- an option in the case of a by-reference type, so we
15339 -- take this path for all Ada dialects if primitive
15340 -- operations are present.
15341 Error_Msg_Sloc
:= Sloc
(DTL
);
15343 ("representation item for& appears after derived type "
15344 & "declaration#", N
);
15346 elsif Has_Primitive_Operations
(Base_Type
(T
)) then
15347 Error_Msg_Sloc
:= Sloc
(DTL
);
15350 ("representation item for& appears after derived type "
15351 & "declaration#??", N
);
15353 ("\may result in implicit conversions for primitive "
15354 & "operations of&??", N
, T
);
15356 ("\to change representations when called with arguments "
15357 & "of type&??", N
, DTL
);
15363 -- No error, link item into head of chain of rep items for the entity,
15364 -- but avoid chaining if we have an overloadable entity, and the pragma
15365 -- is one that can apply to multiple overloaded entities.
15367 if Is_Overloadable
(T
) and then Nkind
(N
) = N_Pragma
then
15369 Pname
: constant Name_Id
:= Pragma_Name
(N
);
15371 if Pname
in Name_Convention | Name_Import | Name_Export
15372 | Name_External | Name_Interface
15379 Record_Rep_Item
(T
, N
);
15381 end Rep_Item_Too_Late
;
15383 -------------------------------------
15384 -- Replace_Type_References_Generic --
15385 -------------------------------------
15387 procedure Replace_Type_References_Generic
(N
: Node_Id
; T
: Entity_Id
) is
15388 TName
: constant Name_Id
:= Chars
(T
);
15390 function Replace_Type_Ref
(N
: Node_Id
) return Traverse_Result
;
15391 -- Processes a single node in the traversal procedure below, checking
15392 -- if node N should be replaced, and if so, doing the replacement.
15394 function Visible_Component
(Comp
: Name_Id
) return Entity_Id
;
15395 -- Given an identifier in the expression, check whether there is a
15396 -- discriminant, component, protected procedure, or entry of the type
15397 -- that is directy visible, and rewrite it as the corresponding selected
15398 -- component of the formal of the subprogram.
15400 ----------------------
15401 -- Replace_Type_Ref --
15402 ----------------------
15404 function Replace_Type_Ref
(N
: Node_Id
) return Traverse_Result
is
15405 Loc
: constant Source_Ptr
:= Sloc
(N
);
15407 procedure Add_Prefix
(Ref
: Node_Id
; Comp
: Entity_Id
);
15408 -- Add the proper prefix to a reference to a component of the type
15409 -- when it is not already a selected component.
15415 procedure Add_Prefix
(Ref
: Node_Id
; Comp
: Entity_Id
) is
15418 Make_Selected_Component
(Loc
,
15419 Prefix
=> New_Occurrence_Of
(T
, Loc
),
15420 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
)));
15421 Replace_Type_Reference
(Prefix
(Ref
));
15430 -- Start of processing for Replace_Type_Ref
15433 if Nkind
(N
) = N_Identifier
then
15435 -- If not the type name, check whether it is a reference to some
15436 -- other type, which must be frozen before the predicate function
15437 -- is analyzed, i.e. before the freeze node of the type to which
15438 -- the predicate applies.
15440 if Chars
(N
) /= TName
then
15441 if Present
(Current_Entity
(N
))
15442 and then Is_Type
(Current_Entity
(N
))
15444 Freeze_Before
(Freeze_Node
(T
), Current_Entity
(N
));
15447 -- The components of the type are directly visible and can
15448 -- be referenced in the source code without a prefix.
15449 -- If a name denoting a component doesn't already have a
15450 -- prefix, then normalize it by adding a reference to the
15451 -- current instance of the type as a prefix.
15453 -- This isn't right in the pathological corner case of an
15454 -- object-declaring expression (e.g., a quantified expression
15455 -- or a declare expression) that declares an object with the
15456 -- same name as a visible component declaration, thereby hiding
15457 -- the component within that expression. For example, given a
15458 -- record with a Boolean component "C" and a dynamic predicate
15459 -- "C = (for some C in Character => Some_Function (C))", only
15460 -- the first of the two uses of C should have a prefix added
15461 -- here; instead, both will get prefixes.
15463 if Nkind
(Parent
(N
)) /= N_Selected_Component
15464 or else N
/= Selector_Name
(Parent
(N
))
15466 Comp
:= Visible_Component
(Chars
(N
));
15468 if Present
(Comp
) then
15469 Add_Prefix
(N
, Comp
);
15475 -- Otherwise do the replacement if this is not a qualified
15476 -- reference to a homograph of the type itself. Note that the
15477 -- current instance could not appear in such a context, e.g.
15478 -- the prefix of a type conversion.
15481 if Nkind
(Parent
(N
)) /= N_Selected_Component
15482 or else N
/= Selector_Name
(Parent
(N
))
15484 Replace_Type_Reference
(N
);
15490 -- Case of selected component, which may be a subcomponent of the
15491 -- current instance, or an expanded name which is still unanalyzed.
15493 elsif Nkind
(N
) = N_Selected_Component
then
15495 -- If selector name is not our type, keep going (we might still
15496 -- have an occurrence of the type in the prefix). If it is a
15497 -- subcomponent of the current entity, add prefix.
15499 if Nkind
(Selector_Name
(N
)) /= N_Identifier
15500 or else Chars
(Selector_Name
(N
)) /= TName
15502 if Nkind
(Prefix
(N
)) = N_Identifier
then
15503 Comp
:= Visible_Component
(Chars
(Prefix
(N
)));
15505 if Present
(Comp
) then
15506 Add_Prefix
(Prefix
(N
), Comp
);
15512 -- Selector name is our type, check qualification
15515 -- Loop through scopes and prefixes, doing comparison
15517 Scop
:= Current_Scope
;
15518 Pref
:= Prefix
(N
);
15520 -- Continue if no more scopes or scope with no name
15522 if No
(Scop
) or else Nkind
(Scop
) not in N_Has_Chars
then
15526 -- Do replace if prefix is an identifier matching the scope
15527 -- that we are currently looking at.
15529 if Nkind
(Pref
) = N_Identifier
15530 and then Chars
(Pref
) = Chars
(Scop
)
15532 Replace_Type_Reference
(N
);
15536 -- Go check scope above us if prefix is itself of the form
15537 -- of a selected component, whose selector matches the scope
15538 -- we are currently looking at.
15540 if Nkind
(Pref
) = N_Selected_Component
15541 and then Nkind
(Selector_Name
(Pref
)) = N_Identifier
15542 and then Chars
(Selector_Name
(Pref
)) = Chars
(Scop
)
15544 Scop
:= Scope
(Scop
);
15545 Pref
:= Prefix
(Pref
);
15547 -- For anything else, we don't have a match, so keep on
15548 -- going, there are still some weird cases where we may
15549 -- still have a replacement within the prefix.
15557 -- Continue for any other node kind
15562 end Replace_Type_Ref
;
15564 procedure Replace_Type_Refs
is new Traverse_Proc
(Replace_Type_Ref
);
15566 -----------------------
15567 -- Visible_Component --
15568 -----------------------
15570 function Visible_Component
(Comp
: Name_Id
) return Entity_Id
is
15574 -- Types with nameable components are record, task, protected types
15576 if Ekind
(T
) in E_Record_Type | E_Task_Type | E_Protected_Type
then
15577 -- This is a sequential search, which seems acceptable
15578 -- efficiency-wise, given the typical size of component
15579 -- lists, protected operation lists, task item lists, and
15580 -- check expressions.
15582 E
:= First_Entity
(T
);
15583 while Present
(E
) loop
15584 if Comes_From_Source
(E
) and then Chars
(E
) = Comp
then
15591 -- Private discriminated types may have visible discriminants
15593 elsif Is_Private_Type
(T
) and then Has_Discriminants
(T
) then
15595 Decl
: constant Node_Id
:= Declaration_Node
(T
);
15600 -- Loop over the discriminants listed in the discriminant part
15601 -- of the private type declaration to find one with a matching
15602 -- name; then, if it exists, return the discriminant entity of
15603 -- the same name in the type, which is that of its full view.
15605 if Nkind
(Decl
) in N_Private_Extension_Declaration
15606 | N_Private_Type_Declaration
15607 and then Present
(Discriminant_Specifications
(Decl
))
15609 Discr
:= First
(Discriminant_Specifications
(Decl
));
15611 while Present
(Discr
) loop
15612 if Chars
(Defining_Identifier
(Discr
)) = Comp
then
15613 Discr
:= First_Discriminant
(T
);
15615 while Present
(Discr
) loop
15616 if Chars
(Discr
) = Comp
then
15620 Next_Discriminant
(Discr
);
15623 pragma Assert
(False);
15632 -- Nothing by that name
15635 end Visible_Component
;
15637 -- Start of processing for Replace_Type_References_Generic
15640 Replace_Type_Refs
(N
);
15641 end Replace_Type_References_Generic
;
15643 --------------------------------
15644 -- Resolve_Aspect_Expressions --
15645 --------------------------------
15647 procedure Resolve_Aspect_Expressions
(E
: Entity_Id
) is
15648 function Resolve_Name
(N
: Node_Id
) return Traverse_Result
;
15649 -- Verify that all identifiers in the expression, with the exception
15650 -- of references to the current entity, denote visible entities. This
15651 -- is done only to detect visibility errors, as the expression will be
15652 -- properly analyzed/expanded during analysis of the predicate function
15653 -- body. We omit quantified expressions from this test, given that they
15654 -- introduce a local identifier that would require proper expansion to
15655 -- handle properly.
15661 function Resolve_Name
(N
: Node_Id
) return Traverse_Result
is
15662 Dummy
: Traverse_Result
;
15665 if Nkind
(N
) = N_Selected_Component
then
15666 if Nkind
(Prefix
(N
)) = N_Identifier
15667 and then Chars
(Prefix
(N
)) /= Chars
(E
)
15669 Find_Selected_Component
(N
);
15674 -- Resolve identifiers that are not selectors in parameter
15675 -- associations (these are never resolved by visibility).
15677 elsif Nkind
(N
) = N_Identifier
15678 and then Chars
(N
) /= Chars
(E
)
15679 and then (Nkind
(Parent
(N
)) /= N_Parameter_Association
15680 or else N
/= Selector_Name
(Parent
(N
)))
15682 Find_Direct_Name
(N
);
15684 -- Reset the Entity if N is overloaded since the entity may not
15685 -- be the correct one.
15687 if Is_Overloaded
(N
) then
15688 Set_Entity
(N
, Empty
);
15691 -- The name in a component association needs no resolution
15693 elsif Nkind
(N
) = N_Component_Association
then
15694 Dummy
:= Resolve_Name
(Expression
(N
));
15697 elsif Nkind
(N
) = N_Quantified_Expression
then
15704 procedure Resolve_Aspect_Expression
is new Traverse_Proc
(Resolve_Name
);
15708 ASN
: Node_Id
:= First_Rep_Item
(E
);
15710 -- Start of processing for Resolve_Aspect_Expressions
15713 while Present
(ASN
) loop
15714 if Nkind
(ASN
) = N_Aspect_Specification
and then Entity
(ASN
) = E
then
15716 A_Id
: constant Aspect_Id
:= Get_Aspect_Id
(ASN
);
15717 Expr
: constant Node_Id
:= Expression
(ASN
);
15722 when Aspect_Aggregate
=>
15723 Resolve_Aspect_Aggregate
(Entity
(ASN
), Expr
);
15725 when Aspect_Stable_Properties
=>
15726 Resolve_Aspect_Stable_Properties
15727 (Entity
(ASN
), Expr
, Class_Present
(ASN
));
15729 -- For now we only deal with aspects that do not generate
15730 -- subprograms, or that may mention current instances of
15731 -- types. These will require special handling???.
15733 when Aspect_Invariant
15734 | Aspect_Predicate_Failure
15738 when Aspect_Dynamic_Predicate
15739 | Aspect_Ghost_Predicate
15741 | Aspect_Static_Predicate
15743 -- Preanalyze expression after type replacement to catch
15744 -- name resolution errors if the predicate function has
15745 -- not been built yet.
15747 -- Note that we cannot use Preanalyze_Spec_Expression
15748 -- directly because of the special handling required for
15749 -- quantifiers (see comments on Resolve_Aspect_Expression
15750 -- above) but we need to emulate it properly.
15752 if No
(Predicate_Function
(E
)) then
15754 Save_In_Spec_Expression
: constant Boolean :=
15755 In_Spec_Expression
;
15756 Save_Full_Analysis
: constant Boolean :=
15759 In_Spec_Expression
:= True;
15760 Full_Analysis
:= False;
15761 Expander_Mode_Save_And_Set
(False);
15763 Resolve_Aspect_Expression
(Expr
);
15765 Expander_Mode_Restore
;
15766 Full_Analysis
:= Save_Full_Analysis
;
15767 In_Spec_Expression
:= Save_In_Spec_Expression
;
15771 when Pre_Post_Aspects
=>
15774 when Aspect_Iterable
=>
15775 if Nkind
(Expr
) = N_Aggregate
then
15780 Assoc
:= First
(Component_Associations
(Expr
));
15781 while Present
(Assoc
) loop
15782 if Nkind
(Expression
(Assoc
)) in N_Has_Entity
15784 Find_Direct_Name
(Expression
(Assoc
));
15792 -- The expression for Default_Value is a static expression
15793 -- of the type, but this expression does not freeze the
15794 -- type, so it can still appear in a representation clause
15795 -- before the actual freeze point.
15797 when Aspect_Default_Value
=>
15798 Set_Must_Not_Freeze
(Expr
);
15799 Preanalyze_Spec_Expression
(Expr
, E
);
15801 when Aspect_Priority
=>
15803 Preanalyze_Spec_Expression
(Expr
, Any_Integer
);
15806 -- Ditto for Storage_Size. Any other aspects that carry
15807 -- expressions that should not freeze ??? This is only
15808 -- relevant to the misuse of deferred constants.
15810 when Aspect_Storage_Size
=>
15811 Set_Must_Not_Freeze
(Expr
);
15812 Preanalyze_Spec_Expression
(Expr
, Any_Integer
);
15815 if Present
(Expr
) then
15816 case Aspect_Argument
(A_Id
) is
15818 | Optional_Expression
15820 Analyze_And_Resolve
(Expr
);
15825 if Nkind
(Expr
) = N_Identifier
then
15826 Find_Direct_Name
(Expr
);
15828 elsif Nkind
(Expr
) = N_Selected_Component
then
15829 Find_Selected_Component
(Expr
);
15837 Next_Rep_Item
(ASN
);
15839 end Resolve_Aspect_Expressions
;
15841 ----------------------------
15842 -- Parse_Aspect_Aggregate --
15843 ----------------------------
15845 procedure Parse_Aspect_Aggregate
15847 Empty_Subp
: in out Node_Id
;
15848 Add_Named_Subp
: in out Node_Id
;
15849 Add_Unnamed_Subp
: in out Node_Id
;
15850 New_Indexed_Subp
: in out Node_Id
;
15851 Assign_Indexed_Subp
: in out Node_Id
)
15853 Assoc
: Node_Id
:= First
(Component_Associations
(N
));
15858 while Present
(Assoc
) loop
15859 Subp
:= Expression
(Assoc
);
15860 Op_Name
:= Chars
(First
(Choices
(Assoc
)));
15861 if Op_Name
= Name_Empty
then
15862 Empty_Subp
:= Subp
;
15864 elsif Op_Name
= Name_Add_Named
then
15865 Add_Named_Subp
:= Subp
;
15867 elsif Op_Name
= Name_Add_Unnamed
then
15868 Add_Unnamed_Subp
:= Subp
;
15870 elsif Op_Name
= Name_New_Indexed
then
15871 New_Indexed_Subp
:= Subp
;
15873 elsif Op_Name
= Name_Assign_Indexed
then
15874 Assign_Indexed_Subp
:= Subp
;
15879 end Parse_Aspect_Aggregate
;
15881 ------------------------------------
15882 -- Parse_Aspect_Stable_Properties --
15883 ------------------------------------
15885 function Parse_Aspect_Stable_Properties
15886 (Aspect_Spec
: Node_Id
; Negated
: out Boolean) return Subprogram_List
15888 function Extract_Entity
(Expr
: Node_Id
) return Entity_Id
;
15889 -- Given an element of a Stable_Properties aspect spec, return the
15890 -- associated entity.
15891 -- This function updates the Negated flag as a side-effect.
15893 --------------------
15894 -- Extract_Entity --
15895 --------------------
15897 function Extract_Entity
(Expr
: Node_Id
) return Entity_Id
is
15900 if Nkind
(Expr
) = N_Op_Not
then
15902 Name
:= Right_Opnd
(Expr
);
15907 if Nkind
(Name
) in N_Has_Entity
then
15908 return Entity
(Name
);
15912 end Extract_Entity
;
15919 -- Start of processing for Parse_Aspect_Stable_Properties
15924 if Nkind
(Aspect_Spec
) /= N_Aggregate
then
15925 return (1 => Extract_Entity
(Aspect_Spec
));
15927 L
:= Expressions
(Aspect_Spec
);
15930 return Result
: Subprogram_List
(1 .. List_Length
(L
)) do
15931 for I
in Result
'Range loop
15932 Result
(I
) := Extract_Entity
(Id
);
15934 if No
(Result
(I
)) then
15935 pragma Assert
(Serious_Errors_Detected
> 0);
15936 goto Ignore_Aspect
;
15944 <<Ignore_Aspect
>> return (1 .. 0 => <>);
15945 end Parse_Aspect_Stable_Properties
;
15947 -------------------------------
15948 -- Validate_Aspect_Aggregate --
15949 -------------------------------
15951 procedure Validate_Aspect_Aggregate
(N
: Node_Id
) is
15952 Empty_Subp
: Node_Id
:= Empty
;
15953 Add_Named_Subp
: Node_Id
:= Empty
;
15954 Add_Unnamed_Subp
: Node_Id
:= Empty
;
15955 New_Indexed_Subp
: Node_Id
:= Empty
;
15956 Assign_Indexed_Subp
: Node_Id
:= Empty
;
15959 Error_Msg_Ada_2022_Feature
("aspect Aggregate", Sloc
(N
));
15961 if Nkind
(N
) /= N_Aggregate
15962 or else Present
(Expressions
(N
))
15963 or else No
(Component_Associations
(N
))
15965 Error_Msg_N
("aspect Aggregate requires an aggregate "
15966 & "with component associations", N
);
15970 Parse_Aspect_Aggregate
(N
,
15971 Empty_Subp
, Add_Named_Subp
, Add_Unnamed_Subp
,
15972 New_Indexed_Subp
, Assign_Indexed_Subp
);
15974 if No
(Empty_Subp
) then
15975 Error_Msg_N
("missing specification for Empty in aggregate", N
);
15978 if Present
(Add_Named_Subp
) then
15979 if Present
(Add_Unnamed_Subp
)
15980 or else Present
(Assign_Indexed_Subp
)
15983 ("conflicting operations for aggregate (RM 4.3.5)", N
);
15987 elsif No
(Add_Named_Subp
)
15988 and then No
(Add_Unnamed_Subp
)
15989 and then No
(Assign_Indexed_Subp
)
15991 Error_Msg_N
("incomplete specification for aggregate", N
);
15993 elsif Present
(New_Indexed_Subp
) /= Present
(Assign_Indexed_Subp
) then
15994 Error_Msg_N
("incomplete specification for indexed aggregate", N
);
15996 end Validate_Aspect_Aggregate
;
15998 -------------------------------
15999 -- Validate_Aspect_Stable_Properties --
16000 -------------------------------
16002 procedure Validate_Aspect_Stable_Properties
16003 (E
: Entity_Id
; N
: Node_Id
; Class_Present
: Boolean)
16005 Is_Aspect_Of_Type
: constant Boolean := Is_Type
(E
);
16007 type Permission
is (Forbidden
, Optional
, Required
);
16008 Modifier_Permission
: Permission
:=
16009 (if Is_Aspect_Of_Type
then Forbidden
else Optional
);
16010 Modifier_Error_Called
: Boolean := False;
16012 procedure Check_Property_Function_Arg
(PF_Arg
: Node_Id
);
16013 -- Check syntax of a property function argument
16015 ----------------------------------
16016 -- Check_Property_Function_Arg --
16017 ----------------------------------
16019 procedure Check_Property_Function_Arg
(PF_Arg
: Node_Id
) is
16020 procedure Modifier_Error
;
16021 -- Generate message about bad "not" modifier if no message already
16022 -- generated. Errors include specifying "not" for an aspect of
16023 -- of a type and specifying "not" for some but not all of the
16024 -- names in a list.
16026 --------------------
16027 -- Modifier_Error --
16028 --------------------
16030 procedure Modifier_Error
is
16032 if Modifier_Error_Called
then
16033 return; -- error message already generated
16036 Modifier_Error_Called
:= True;
16038 if Is_Aspect_Of_Type
then
16040 ("NOT modifier not allowed for Stable_Properties aspect"
16041 & " of a type", PF_Arg
);
16043 Error_Msg_N
("mixed use of NOT modifiers", PF_Arg
);
16045 end Modifier_Error
;
16047 PF_Name
: Node_Id
:= PF_Arg
;
16049 -- Start of processing for Check_Property_Function_Arg
16052 if Nkind
(PF_Arg
) = N_Op_Not
then
16053 PF_Name
:= Right_Opnd
(PF_Arg
);
16055 case Modifier_Permission
is
16059 Modifier_Permission
:= Required
;
16064 case Modifier_Permission
is
16068 Modifier_Permission
:= Forbidden
;
16074 if Nkind
(PF_Name
) not in
16075 N_Identifier | N_Operator_Symbol | N_Selected_Component
16077 Error_Msg_N
("bad property function name", PF_Name
);
16079 end Check_Property_Function_Arg
;
16081 -- Start of processing for Validate_Aspect_Stable_Properties
16084 Error_Msg_Ada_2022_Feature
("aspect Stable_Properties", Sloc
(N
));
16086 if not Is_Aspect_Of_Type
and then not Is_Subprogram
(E
) then
16087 Error_Msg_N
("Stable_Properties aspect can only be specified for "
16088 & "a type or a subprogram", N
);
16089 elsif Class_Present
then
16090 if Is_Aspect_Of_Type
then
16091 if not Is_Tagged_Type
(E
) then
16093 ("Stable_Properties''Class aspect cannot be specified for "
16094 & "an untagged type", N
);
16097 if not Is_Dispatching_Operation
(E
) then
16099 ("Stable_Properties''Class aspect cannot be specified for "
16100 & "a subprogram that is not a primitive subprogram "
16101 & "of a tagged type", N
);
16106 if Nkind
(N
) = N_Aggregate
then
16107 if Present
(Component_Associations
(N
))
16108 or else Null_Record_Present
(N
)
16109 or else not Present
(Expressions
(N
))
16111 Error_Msg_N
("bad Stable_Properties aspect specification", N
);
16116 PF_Arg
: Node_Id
:= First
(Expressions
(N
));
16118 while Present
(PF_Arg
) loop
16119 Check_Property_Function_Arg
(PF_Arg
);
16124 Check_Property_Function_Arg
(N
);
16126 end Validate_Aspect_Stable_Properties
;
16128 --------------------------------
16129 -- Resolve_Iterable_Operation --
16130 --------------------------------
16132 procedure Resolve_Iterable_Operation
16134 Cursor
: Entity_Id
;
16143 if not Is_Overloaded
(N
) then
16144 if not Is_Entity_Name
(N
)
16145 or else Ekind
(Entity
(N
)) /= E_Function
16146 or else Scope
(Entity
(N
)) /= Scope
(Typ
)
16147 or else No
(First_Formal
(Entity
(N
)))
16148 or else Etype
(First_Formal
(Entity
(N
))) /= Typ
16151 ("iterable primitive must be local function name whose first "
16152 & "formal is an iterable type", N
);
16157 F1
:= First_Formal
(Ent
);
16158 F2
:= Next_Formal
(F1
);
16160 if Nam
= Name_First
then
16162 -- First (Container) => Cursor
16164 if Etype
(Ent
) /= Cursor
then
16165 Error_Msg_N
("primitive for First must yield a cursor", N
);
16166 elsif Present
(F2
) then
16167 Error_Msg_N
("no match for First iterable primitive", N
);
16170 elsif Nam
= Name_Last
then
16172 -- Last (Container) => Cursor
16174 if Etype
(Ent
) /= Cursor
then
16175 Error_Msg_N
("primitive for Last must yield a cursor", N
);
16176 elsif Present
(F2
) then
16177 Error_Msg_N
("no match for Last iterable primitive", N
);
16180 elsif Nam
= Name_Next
then
16182 -- Next (Container, Cursor) => Cursor
16185 or else Etype
(F2
) /= Cursor
16186 or else Etype
(Ent
) /= Cursor
16187 or else Present
(Next_Formal
(F2
))
16189 Error_Msg_N
("no match for Next iterable primitive", N
);
16192 elsif Nam
= Name_Previous
then
16194 -- Previous (Container, Cursor) => Cursor
16197 or else Etype
(F2
) /= Cursor
16198 or else Etype
(Ent
) /= Cursor
16199 or else Present
(Next_Formal
(F2
))
16201 Error_Msg_N
("no match for Previous iterable primitive", N
);
16204 elsif Nam
= Name_Has_Element
then
16206 -- Has_Element (Container, Cursor) => Boolean
16209 or else Etype
(F2
) /= Cursor
16210 or else Etype
(Ent
) /= Standard_Boolean
16211 or else Present
(Next_Formal
(F2
))
16213 Error_Msg_N
("no match for Has_Element iterable primitive", N
);
16216 elsif Nam
= Name_Element
then
16218 -- Element (Container, Cursor) => Element_Type;
16221 or else Etype
(F2
) /= Cursor
16222 or else Present
(Next_Formal
(F2
))
16224 Error_Msg_N
("no match for Element iterable primitive", N
);
16228 raise Program_Error
;
16232 -- Overloaded case: find subprogram with proper signature. Caller
16233 -- will report error if no match is found.
16240 Get_First_Interp
(N
, I
, It
);
16241 while Present
(It
.Typ
) loop
16242 if Ekind
(It
.Nam
) = E_Function
16243 and then Scope
(It
.Nam
) = Scope
(Typ
)
16244 and then Present
(First_Formal
(It
.Nam
))
16245 and then Etype
(First_Formal
(It
.Nam
)) = Typ
16247 F1
:= First_Formal
(It
.Nam
);
16249 if Nam
= Name_First
then
16250 if Etype
(It
.Nam
) = Cursor
16251 and then No
(Next_Formal
(F1
))
16253 Set_Entity
(N
, It
.Nam
);
16257 elsif Nam
= Name_Next
then
16258 F2
:= Next_Formal
(F1
);
16261 and then No
(Next_Formal
(F2
))
16262 and then Etype
(F2
) = Cursor
16263 and then Etype
(It
.Nam
) = Cursor
16265 Set_Entity
(N
, It
.Nam
);
16269 elsif Nam
= Name_Has_Element
then
16270 F2
:= Next_Formal
(F1
);
16273 and then No
(Next_Formal
(F2
))
16274 and then Etype
(F2
) = Cursor
16275 and then Etype
(It
.Nam
) = Standard_Boolean
16277 Set_Entity
(N
, It
.Nam
);
16278 F2
:= Next_Formal
(F1
);
16282 elsif Nam
= Name_Element
then
16283 F2
:= Next_Formal
(F1
);
16286 and then No
(Next_Formal
(F2
))
16287 and then Etype
(F2
) = Cursor
16289 Set_Entity
(N
, It
.Nam
);
16295 Get_Next_Interp
(I
, It
);
16299 end Resolve_Iterable_Operation
;
16301 ------------------------------
16302 -- Resolve_Aspect_Aggregate --
16303 ------------------------------
16305 procedure Resolve_Aspect_Aggregate
16309 function Valid_Empty
(E
: Entity_Id
) return Boolean;
16310 function Valid_Add_Named
(E
: Entity_Id
) return Boolean;
16311 function Valid_Add_Unnamed
(E
: Entity_Id
) return Boolean;
16312 function Valid_New_Indexed
(E
: Entity_Id
) return Boolean;
16313 function Valid_Assign_Indexed
(E
: Entity_Id
) return Boolean;
16314 -- Predicates that establish the legality of each possible operation in
16315 -- an Aggregate aspect.
16318 with function Pred
(Id
: Node_Id
) return Boolean;
16319 procedure Resolve_Operation
(Subp_Id
: Node_Id
);
16320 -- Common processing to resolve each aggregate operation.
16322 ------------------------
16323 -- Valid_Assign_Index --
16324 ------------------------
16326 function Valid_Assign_Indexed
(E
: Entity_Id
) return Boolean is
16328 -- The profile must be the same as for Add_Named, with the added
16329 -- requirement that the key_type be a discrete type.
16331 if Valid_Add_Named
(E
) then
16332 return Is_Discrete_Type
(Etype
(Next_Formal
(First_Formal
(E
))));
16336 end Valid_Assign_Indexed
;
16342 function Valid_Empty
(E
: Entity_Id
) return Boolean is
16344 if Etype
(E
) /= Typ
or else Scope
(E
) /= Scope
(Typ
) then
16347 elsif Ekind
(E
) = E_Constant
then
16350 elsif Ekind
(E
) = E_Function
then
16351 return No
(First_Formal
(E
))
16353 (Is_Integer_Type
(Etype
(First_Formal
(E
)))
16354 and then No
(Next_Formal
(First_Formal
(E
))));
16360 ---------------------
16361 -- Valid_Add_Named --
16362 ---------------------
16364 function Valid_Add_Named
(E
: Entity_Id
) return Boolean is
16365 F2
, F3
: Entity_Id
;
16367 if Ekind
(E
) = E_Procedure
16368 and then Scope
(E
) = Scope
(Typ
)
16369 and then Number_Formals
(E
) = 3
16370 and then Etype
(First_Formal
(E
)) = Typ
16371 and then Ekind
(First_Formal
(E
)) = E_In_Out_Parameter
16373 F2
:= Next_Formal
(First_Formal
(E
));
16374 F3
:= Next_Formal
(F2
);
16375 return Ekind
(F2
) = E_In_Parameter
16376 and then Ekind
(F3
) = E_In_Parameter
16377 and then not Is_Limited_Type
(Etype
(F2
))
16378 and then not Is_Limited_Type
(Etype
(F3
));
16382 end Valid_Add_Named
;
16384 -----------------------
16385 -- Valid_Add_Unnamed --
16386 -----------------------
16388 function Valid_Add_Unnamed
(E
: Entity_Id
) return Boolean is
16390 return Ekind
(E
) = E_Procedure
16391 and then Scope
(E
) = Scope
(Typ
)
16392 and then Number_Formals
(E
) = 2
16393 and then Etype
(First_Formal
(E
)) = Typ
16394 and then Ekind
(First_Formal
(E
)) = E_In_Out_Parameter
16396 not Is_Limited_Type
(Etype
(Next_Formal
(First_Formal
(E
))));
16397 end Valid_Add_Unnamed
;
16399 -----------------------
16400 -- Valid_Nmw_Indexed --
16401 -----------------------
16403 function Valid_New_Indexed
(E
: Entity_Id
) return Boolean is
16405 return Ekind
(E
) = E_Function
16406 and then Scope
(E
) = Scope
(Typ
)
16407 and then Etype
(E
) = Typ
16408 and then Number_Formals
(E
) = 2
16409 and then Is_Discrete_Type
(Etype
(First_Formal
(E
)))
16410 and then Etype
(First_Formal
(E
)) =
16411 Etype
(Next_Formal
(First_Formal
(E
)));
16412 end Valid_New_Indexed
;
16414 -----------------------
16415 -- Resolve_Operation --
16416 -----------------------
16418 procedure Resolve_Operation
(Subp_Id
: Node_Id
) is
16425 if not Is_Overloaded
(Subp_Id
) then
16426 Subp
:= Entity
(Subp_Id
);
16427 if not Pred
(Subp
) then
16429 ("improper aggregate operation for&", Subp_Id
, Typ
);
16433 Set_Entity
(Subp_Id
, Empty
);
16434 Get_First_Interp
(Subp_Id
, I
, It
);
16435 while Present
(It
.Nam
) loop
16436 if Pred
(It
.Nam
) then
16437 Set_Is_Overloaded
(Subp_Id
, False);
16438 Set_Entity
(Subp_Id
, It
.Nam
);
16442 Get_Next_Interp
(I
, It
);
16445 if No
(Entity
(Subp_Id
)) then
16447 ("improper aggregate operation for&", Subp_Id
, Typ
);
16450 end Resolve_Operation
;
16456 procedure Resolve_Empty
is new Resolve_Operation
(Valid_Empty
);
16457 procedure Resolve_Unnamed
is new Resolve_Operation
(Valid_Add_Unnamed
);
16458 procedure Resolve_Named
is new Resolve_Operation
(Valid_Add_Named
);
16459 procedure Resolve_Indexed
is new Resolve_Operation
(Valid_New_Indexed
);
16460 procedure Resolve_Assign_Indexed
16461 is new Resolve_Operation
16462 (Valid_Assign_Indexed
);
16464 -- Start of processing for Resolve_Aspect_Aggregate
16467 Assoc
:= First
(Component_Associations
(Expr
));
16469 while Present
(Assoc
) loop
16470 Op_Name
:= Chars
(First
(Choices
(Assoc
)));
16472 -- When verifying the consistency of aspects between the freeze point
16473 -- and the end of declarations, we use a copy which is not analyzed
16474 -- yet, so do it now.
16476 Subp_Id
:= Expression
(Assoc
);
16477 if No
(Etype
(Subp_Id
)) then
16481 if Op_Name
= Name_Empty
then
16482 Resolve_Empty
(Subp_Id
);
16484 elsif Op_Name
= Name_Add_Named
then
16485 Resolve_Named
(Subp_Id
);
16487 elsif Op_Name
= Name_Add_Unnamed
then
16488 Resolve_Unnamed
(Subp_Id
);
16490 elsif Op_Name
= Name_New_Indexed
then
16491 Resolve_Indexed
(Subp_Id
);
16493 elsif Op_Name
= Name_Assign_Indexed
then
16494 Resolve_Assign_Indexed
(Subp_Id
);
16499 end Resolve_Aspect_Aggregate
;
16501 --------------------------------------
16502 -- Resolve_Aspect_Stable_Properties --
16503 --------------------------------------
16505 procedure Resolve_Aspect_Stable_Properties
16506 (Typ_Or_Subp
: Entity_Id
; Expr
: Node_Id
; Class_Present
: Boolean)
16508 Is_Aspect_Of_Type
: constant Boolean := Is_Type
(Typ_Or_Subp
);
16510 Singleton
: constant Boolean := Nkind
(Expr
) /= N_Aggregate
;
16511 Subp_Name
: Node_Id
:= (if Singleton
16513 else First
(Expressions
(Expr
)));
16516 if Is_Aspect_Of_Type
16517 and then Has_Private_Declaration
(Typ_Or_Subp
)
16518 and then not Is_Private_Type
(Typ_Or_Subp
)
16521 ("Stable_Properties aspect cannot be specified " &
16522 "for the completion of a private type", Typ_Or_Subp
);
16525 -- Analogous checks that the aspect is not specified for a completion
16526 -- in the subprogram case are not performed here because they are not
16527 -- specific to this particular aspect. Right ???
16530 Has_Not
:= Nkind
(Subp_Name
) = N_Op_Not
;
16532 Set_Analyzed
(Subp_Name
); -- ???
16533 Subp_Name
:= Right_Opnd
(Subp_Name
);
16536 if No
(Etype
(Subp_Name
)) then
16537 Analyze
(Subp_Name
);
16541 Subp
: Entity_Id
:= Empty
;
16546 function Is_Property_Function
(E
: Entity_Id
) return Boolean;
16547 -- Implements RM 7.3.4 definition of "property function"
16549 --------------------------
16550 -- Is_Property_Function --
16551 --------------------------
16553 function Is_Property_Function
(E
: Entity_Id
) return Boolean is
16555 if Ekind
(E
) not in E_Function | E_Operator
16556 or else Number_Formals
(E
) /= 1
16562 Param_Type
: constant Entity_Id
:=
16563 Base_Type
(Etype
(First_Formal
(E
)));
16565 function Matches_Param_Type
(Typ
: Entity_Id
)
16567 (Base_Type
(Typ
) = Param_Type
16569 (Is_Class_Wide_Type
(Param_Type
)
16570 and then Is_Ancestor
(Root_Type
(Param_Type
),
16571 Base_Type
(Typ
))));
16573 if Is_Aspect_Of_Type
then
16574 if Matches_Param_Type
(Typ_Or_Subp
) then
16577 elsif Is_Primitive
(Typ_Or_Subp
) then
16579 Formal
: Entity_Id
:= First_Formal
(Typ_Or_Subp
);
16581 while Present
(Formal
) loop
16582 if Matches_Param_Type
(Etype
(Formal
)) then
16584 -- Test whether Typ_Or_Subp (which is a subp
16585 -- in this case) is primitive op of the type
16586 -- of this parameter.
16587 if Scope
(Typ_Or_Subp
) = Scope
(Param_Type
) then
16591 Next_Formal
(Formal
);
16598 end Is_Property_Function
;
16600 if not Is_Overloaded
(Subp_Name
) then
16601 Subp
:= Entity
(Subp_Name
);
16602 if not Is_Property_Function
(Subp
) then
16603 Error_Msg_NE
("improper property function for&",
16604 Subp_Name
, Typ_Or_Subp
);
16608 Set_Entity
(Subp_Name
, Empty
);
16609 Get_First_Interp
(Subp_Name
, I
, It
);
16610 while Present
(It
.Nam
) loop
16611 if Is_Property_Function
(It
.Nam
) then
16612 if Present
(Subp
) then
16614 ("ambiguous property function name for&",
16615 Subp_Name
, Typ_Or_Subp
);
16620 Set_Is_Overloaded
(Subp_Name
, False);
16621 Set_Entity
(Subp_Name
, Subp
);
16624 Get_Next_Interp
(I
, It
);
16628 Error_Msg_NE
("improper property function for&",
16629 Subp_Name
, Typ_Or_Subp
);
16634 -- perform legality (as opposed to name resolution) Subp checks
16636 if Is_Limited_Type
(Etype
(Subp
)) then
16638 ("result type of property function for& is limited",
16639 Subp_Name
, Typ_Or_Subp
);
16642 if Ekind
(First_Formal
(Subp
)) /= E_In_Parameter
then
16644 ("mode of parameter of property function for& is not IN",
16645 Subp_Name
, Typ_Or_Subp
);
16648 if Is_Class_Wide_Type
(Etype
(First_Formal
(Subp
))) then
16649 if not Covers
(Etype
(First_Formal
(Subp
)), Typ_Or_Subp
) then
16651 ("class-wide parameter type of property function " &
16652 "for& does not cover the type",
16653 Subp_Name
, Typ_Or_Subp
);
16655 -- ??? This test is slightly stricter than 7.3.4(12/5);
16656 -- some legal corner cases may be incorrectly rejected.
16657 elsif Scope
(Subp
) /= Scope
(Etype
(First_Formal
(Subp
)))
16660 ("property function for& not declared in same scope " &
16661 "as parameter type",
16662 Subp_Name
, Typ_Or_Subp
);
16664 elsif Is_Aspect_Of_Type
and then
16665 Scope
(Subp
) /= Scope
(Typ_Or_Subp
) and then
16666 Scope
(Subp
) /= Standard_Standard
-- e.g., derived type's "abs"
16669 ("property function for& " &
16670 "not a primitive function of the type",
16671 Subp_Name
, Typ_Or_Subp
);
16675 -- check that Subp was mentioned in param type's aspect spec
16677 Param_Type
: constant Entity_Id
:=
16678 Base_Type
(Etype
(First_Formal
(Subp
)));
16679 Aspect_Spec
: constant Node_Id
:=
16680 Find_Value_Of_Aspect
16681 (Param_Type
, Aspect_Stable_Properties
,
16682 Class_Present
=> Class_Present
);
16683 Found
: Boolean := False;
16685 if Present
(Aspect_Spec
) then
16688 SPF_List
: constant Subprogram_List
:=
16689 Parse_Aspect_Stable_Properties
16690 (Aspect_Spec
, Negated
=> Ignored
);
16692 Found
:= (for some E
of SPF_List
=> E
= Subp
);
16693 -- look through renamings ???
16698 CW_Modifier
: constant String :=
16699 (if Class_Present
then "class-wide " else "");
16703 & "property function for& mentioned after NOT "
16706 & "stable property function of its parameter type",
16707 Subp_Name
, Typ_Or_Subp
);
16714 exit when Singleton
;
16716 Next
((if Has_Not
then Parent
(Subp_Name
) else Subp_Name
));
16717 exit when No
(Subp_Name
);
16720 Set_Analyzed
(Expr
);
16721 end Resolve_Aspect_Stable_Properties
;
16723 -----------------------------------------
16724 -- Resolve_Storage_Model_Type_Argument --
16725 -----------------------------------------
16727 procedure Resolve_Storage_Model_Type_Argument
16730 Addr_Type
: in out Entity_Id
;
16734 type Formal_Profile
is record
16736 Mode
: Formal_Kind
;
16739 type Formal_Profiles
is array (Positive range <>) of Formal_Profile
;
16741 function Aspect_Argument_Profile_Matches
16743 Profiles
: Formal_Profiles
;
16744 Result_Subt
: Entity_Id
;
16745 Err_On_Mismatch
: Boolean) return Boolean;
16746 -- Checks that the formal parameters of subprogram Subp conform to the
16747 -- subtypes and modes specified by Profiles, as well as to the result
16748 -- subtype Result_Subt when that is nonempty.
16750 function Aspect_Argument_Profile_Matches
16752 Profiles
: Formal_Profiles
;
16753 Result_Subt
: Entity_Id
;
16754 Err_On_Mismatch
: Boolean) return Boolean
16757 procedure Report_Argument_Error
16759 Formal
: Entity_Id
:= Empty
;
16760 Subt
: Entity_Id
:= Empty
);
16761 -- If Err_On_Mismatch is True, reports an argument error given by Msg
16762 -- associated with Formal and/or Subt.
16764 procedure Report_Argument_Error
16766 Formal
: Entity_Id
:= Empty
;
16767 Subt
: Entity_Id
:= Empty
)
16770 if Err_On_Mismatch
then
16771 if Present
(Formal
) then
16772 if Present
(Subt
) then
16773 Error_Msg_Node_2
:= Subt
;
16775 Error_Msg_NE
(Msg
, N
, Formal
);
16777 elsif Present
(Subt
) then
16778 Error_Msg_NE
(Msg
, N
, Subt
);
16781 Error_Msg_N
(Msg
, N
);
16784 end Report_Argument_Error
;
16788 Formal
: Entity_Id
:= First_Formal
(Subp
);
16789 Is_Error
: Boolean := False;
16791 -- Start of processing for Aspect_Argument_Profile_Matches
16794 for FP
of Profiles
loop
16795 if No
(Formal
) then
16797 Report_Argument_Error
("missing formal of }", Subt
=> FP
.Subt
);
16800 elsif not Subtypes_Statically_Match
16801 (Etype
(Formal
), FP
.Subt
)
16804 Report_Argument_Error
16805 ("formal& must be of subtype&",
16806 Formal
=> Formal
, Subt
=> FP
.Subt
);
16809 elsif Ekind
(Formal
) /= FP
.Mode
then
16811 Report_Argument_Error
16812 ("formal& has wrong mode", Formal
=> Formal
);
16816 Formal
:= Next_Formal
(Formal
);
16820 and then Present
(Formal
)
16823 Report_Argument_Error
16824 ("too many formals for subprogram in aspect");
16828 and then Present
(Result_Subt
)
16829 and then not Subtypes_Statically_Match
(Etype
(Subp
), Result_Subt
)
16832 Report_Argument_Error
16833 ("subprogram must have result}", Subt
=> Result_Subt
);
16836 return not Is_Error
;
16837 end Aspect_Argument_Profile_Matches
;
16843 Storage_Count_Type
: constant Entity_Id
:= RTE
(RE_Storage_Count
);
16844 System_Address_Type
: constant Entity_Id
:= RTE
(RE_Address
);
16846 -- Start of processing for Resolve_Storage_Model_Type_Argument
16849 if Nam
= Name_Address_Type
then
16850 if not Is_Entity_Name
(N
)
16851 or else not Is_Type
(Entity
(N
))
16852 or else (Root_Type
(Entity
(N
)) /= System_Address_Type
16853 and then not Is_Integer_Type
(Entity
(N
)))
16855 Error_Msg_N
("named entity must be a descendant of System.Address "
16856 & "or an integer type", N
);
16859 Addr_Type
:= Entity
(N
);
16863 -- If Addr_Type is not present as the first association, then we default
16864 -- it to System.Address.
16866 elsif No
(Addr_Type
) then
16867 Addr_Type
:= RTE
(RE_Address
);
16870 if Nam
= Name_Null_Address
then
16871 if not Is_Entity_Name
(N
)
16872 or else not Is_Constant_Object
(Entity
(N
))
16874 not Subtypes_Statically_Match
(Etype
(Entity
(N
)), Addr_Type
)
16877 ("named entity must be constant of subtype}", N
, Addr_Type
);
16882 elsif not Is_Overloaded
(N
) then
16883 if not Is_Entity_Name
(N
)
16884 or else Ekind
(Entity
(N
)) not in E_Function | E_Procedure
16885 or else Scope
(Entity
(N
)) /= Scope
(Typ
)
16887 Error_Msg_N
("argument must be local subprogram name", N
);
16893 if Nam
= Name_Allocate
then
16894 if not Aspect_Argument_Profile_Matches
16897 ((Typ
, E_In_Out_Parameter
),
16898 (Addr_Type
, E_Out_Parameter
),
16899 (Storage_Count_Type
, E_In_Parameter
),
16900 (Storage_Count_Type
, E_In_Parameter
)),
16901 Result_Subt
=> Empty
,
16902 Err_On_Mismatch
=> True)
16904 Error_Msg_N
("no match for Allocate operation", N
);
16907 elsif Nam
= Name_Deallocate
then
16908 if not Aspect_Argument_Profile_Matches
16911 ((Typ
, E_In_Out_Parameter
),
16912 (Addr_Type
, E_In_Parameter
),
16913 (Storage_Count_Type
, E_In_Parameter
),
16914 (Storage_Count_Type
, E_In_Parameter
)),
16915 Result_Subt
=> Empty
,
16916 Err_On_Mismatch
=> True)
16918 Error_Msg_N
("no match for Deallocate operation", N
);
16921 elsif Nam
= Name_Copy_From
then
16922 if not Aspect_Argument_Profile_Matches
16925 ((Typ
, E_In_Out_Parameter
),
16926 (System_Address_Type
, E_In_Parameter
),
16927 (Addr_Type
, E_In_Parameter
),
16928 (Storage_Count_Type
, E_In_Parameter
)),
16929 Result_Subt
=> Empty
,
16930 Err_On_Mismatch
=> True)
16932 Error_Msg_N
("no match for Copy_From operation", N
);
16935 elsif Nam
= Name_Copy_To
then
16936 if not Aspect_Argument_Profile_Matches
16939 ((Typ
, E_In_Out_Parameter
),
16940 (Addr_Type
, E_In_Parameter
),
16941 (System_Address_Type
, E_In_Parameter
),
16942 (Storage_Count_Type
, E_In_Parameter
)),
16943 Result_Subt
=> Empty
,
16944 Err_On_Mismatch
=> True)
16946 Error_Msg_N
("no match for Copy_To operation", N
);
16949 elsif Nam
= Name_Storage_Size
then
16950 if not Aspect_Argument_Profile_Matches
16952 Profiles
=> (1 => (Typ
, E_In_Parameter
)),
16953 Result_Subt
=> Storage_Count_Type
,
16954 Err_On_Mismatch
=> True)
16956 Error_Msg_N
("no match for Storage_Size operation", N
);
16960 null; -- Error will be caught in Validate_Storage_Model_Type_Aspect
16964 -- Overloaded case: find subprogram with proper signature
16969 Found_Match
: Boolean := False;
16972 Get_First_Interp
(N
, I
, It
);
16973 while Present
(It
.Typ
) loop
16974 if Ekind
(It
.Nam
) in E_Function | E_Procedure
16975 and then Scope
(It
.Nam
) = Scope
(Typ
)
16977 if Nam
= Name_Allocate
then
16979 Aspect_Argument_Profile_Matches
16982 ((Typ
, E_In_Out_Parameter
),
16983 (Addr_Type
, E_Out_Parameter
),
16984 (Storage_Count_Type
, E_In_Parameter
),
16985 (Storage_Count_Type
, E_In_Parameter
)),
16986 Result_Subt
=> Empty
,
16987 Err_On_Mismatch
=> False);
16989 elsif Nam
= Name_Deallocate
then
16991 Aspect_Argument_Profile_Matches
16994 ((Typ
, E_In_Out_Parameter
),
16995 (Addr_Type
, E_In_Parameter
),
16996 (Storage_Count_Type
, E_In_Parameter
),
16997 (Storage_Count_Type
, E_In_Parameter
)),
16998 Result_Subt
=> Empty
,
16999 Err_On_Mismatch
=> False);
17001 elsif Nam
= Name_Copy_From
then
17003 Aspect_Argument_Profile_Matches
17006 ((Typ
, E_In_Out_Parameter
),
17007 (System_Address_Type
, E_In_Parameter
),
17008 (Addr_Type
, E_In_Parameter
),
17009 (Storage_Count_Type
, E_In_Parameter
),
17010 (Storage_Count_Type
, E_In_Parameter
)),
17011 Result_Subt
=> Empty
,
17012 Err_On_Mismatch
=> False);
17014 elsif Nam
= Name_Copy_To
then
17016 Aspect_Argument_Profile_Matches
17019 ((Typ
, E_In_Out_Parameter
),
17020 (Addr_Type
, E_In_Parameter
),
17021 (Storage_Count_Type
, E_In_Parameter
),
17022 (System_Address_Type
, E_In_Parameter
),
17023 (Storage_Count_Type
, E_In_Parameter
)),
17024 Result_Subt
=> Empty
,
17025 Err_On_Mismatch
=> False);
17027 elsif Nam
= Name_Storage_Size
then
17029 Aspect_Argument_Profile_Matches
17031 Profiles
=> (1 => (Typ
, E_In_Parameter
)),
17032 Result_Subt
=> Storage_Count_Type
,
17033 Err_On_Mismatch
=> False);
17036 if Found_Match
then
17037 Set_Entity
(N
, It
.Nam
);
17042 Get_Next_Interp
(I
, It
);
17045 if not Found_Match
then
17047 ("no match found for Storage_Model_Type operation", N
);
17051 end Resolve_Storage_Model_Type_Argument
;
17057 procedure Set_Biased
17061 Biased
: Boolean := True)
17065 Set_Has_Biased_Representation
(E
);
17067 if Warn_On_Biased_Representation
then
17069 ("?.b?" & Msg
& " forces biased representation for&", N
, E
);
17074 --------------------
17075 -- Set_Enum_Esize --
17076 --------------------
17078 procedure Set_Enum_Esize
(T
: Entity_Id
) is
17084 Reinit_Alignment
(T
);
17086 -- Find the minimum standard size (8,16,32,64,128) that fits
17088 Lo
:= Enumeration_Rep
(Entity
(Type_Low_Bound
(T
)));
17089 Hi
:= Enumeration_Rep
(Entity
(Type_High_Bound
(T
)));
17092 if Lo
>= -Uint_2
**7 and then Hi
< Uint_2
**7 then
17093 Sz
:= UI_From_Int
(Standard_Character_Size
);
17094 -- Might be > 8 on some targets
17096 elsif Lo
>= -Uint_2
**15 and then Hi
< Uint_2
**15 then
17099 elsif Lo
>= -Uint_2
**31 and then Hi
< Uint_2
**31 then
17102 elsif Lo
>= -Uint_2
**63 and then Hi
< Uint_2
**63 then
17105 else pragma Assert
(Lo
>= -Uint_2
**127 and then Hi
< Uint_2
**127);
17110 if Hi
< Uint_2
**8 then
17111 Sz
:= UI_From_Int
(Standard_Character_Size
);
17113 elsif Hi
< Uint_2
**16 then
17116 elsif Hi
< Uint_2
**32 then
17119 elsif Hi
< Uint_2
**64 then
17122 else pragma Assert
(Hi
< Uint_2
**128);
17127 -- That minimum is the proper size unless we have a foreign convention
17128 -- and the size required is 32 or less, in which case we bump the size
17129 -- up to 32. This is required for C and C++ and seems reasonable for
17130 -- all other foreign conventions.
17132 if Has_Foreign_Convention
(T
)
17133 and then Esize
(T
) < Standard_Integer_Size
17135 -- Don't do this if Short_Enums on target
17137 and then not Target_Short_Enums
17139 Set_Esize
(T
, UI_From_Int
(Standard_Integer_Size
));
17143 end Set_Enum_Esize
;
17145 -----------------------------
17146 -- Uninstall_Discriminants --
17147 -----------------------------
17149 procedure Uninstall_Discriminants
(E
: Entity_Id
) is
17155 -- Discriminants have been made visible for type declarations and
17156 -- protected type declarations, not for subtype declarations.
17158 if Nkind
(Parent
(E
)) /= N_Subtype_Declaration
then
17159 Disc
:= First_Discriminant
(E
);
17160 while Present
(Disc
) loop
17161 if Disc
/= Current_Entity
(Disc
) then
17162 Prev
:= Current_Entity
(Disc
);
17163 while Present
(Prev
)
17164 and then Present
(Homonym
(Prev
))
17165 and then Homonym
(Prev
) /= Disc
17167 Prev
:= Homonym
(Prev
);
17173 Set_Is_Immediately_Visible
(Disc
, False);
17175 Outer
:= Homonym
(Disc
);
17176 while Present
(Outer
) and then Scope
(Outer
) = E
loop
17177 Outer
:= Homonym
(Outer
);
17180 -- Reset homonym link of other entities, but do not modify link
17181 -- between entities in current scope, so that the back end can
17182 -- have a proper count of local overloadings.
17185 Set_Name_Entity_Id
(Chars
(Disc
), Outer
);
17187 elsif Scope
(Prev
) /= Scope
(Disc
) then
17188 Set_Homonym
(Prev
, Outer
);
17191 Next_Discriminant
(Disc
);
17194 end Uninstall_Discriminants
;
17196 ------------------------------
17197 -- Validate_Address_Clauses --
17198 ------------------------------
17200 procedure Validate_Address_Clauses
is
17201 function Offset_Value
(Expr
: Node_Id
) return Uint
;
17202 -- Given an Address attribute reference, return the value in bits of its
17203 -- offset from the first bit of the underlying entity, or 0 if it is not
17204 -- known at compile time.
17210 function Offset_Value
(Expr
: Node_Id
) return Uint
is
17211 N
: Node_Id
:= Prefix
(Expr
);
17213 Val
: Uint
:= Uint_0
;
17216 -- Climb the prefix chain and compute the cumulative offset
17219 if Is_Entity_Name
(N
) then
17222 elsif Nkind
(N
) = N_Selected_Component
then
17223 Off
:= Component_Bit_Offset
(Entity
(Selector_Name
(N
)));
17224 if Present
(Off
) and then Off
>= Uint_0
then
17231 elsif Nkind
(N
) = N_Indexed_Component
then
17232 Off
:= Indexed_Component_Bit_Offset
(N
);
17233 if Present
(Off
) then
17246 -- Start of processing for Validate_Address_Clauses
17249 for J
in Address_Clause_Checks
.First
.. Address_Clause_Checks
.Last
loop
17251 ACCR
: Address_Clause_Check_Record
17252 renames Address_Clause_Checks
.Table
(J
);
17256 X_Alignment
: Uint
;
17257 Y_Alignment
: Uint
:= Uint_0
;
17260 Y_Size
: Uint
:= Uint_0
;
17265 -- Skip processing of this entry if warning already posted, or if
17266 -- alignments are not set.
17268 if not Address_Warning_Posted
(ACCR
.N
)
17269 and then Known_Alignment
(ACCR
.X
)
17270 and then Known_Alignment
(ACCR
.Y
)
17272 Expr
:= Original_Node
(Expression
(ACCR
.N
));
17274 -- Get alignments, sizes and offset, if any
17276 X_Alignment
:= Alignment
(ACCR
.X
);
17277 X_Size
:= Esize
(ACCR
.X
);
17279 if Present
(ACCR
.Y
) then
17280 Y_Alignment
:= Alignment
(ACCR
.Y
);
17282 (if Known_Esize
(ACCR
.Y
) then Esize
(ACCR
.Y
) else Uint_0
);
17286 and then Nkind
(Expr
) = N_Attribute_Reference
17287 and then Attribute_Name
(Expr
) = Name_Address
17289 X_Offs
:= Offset_Value
(Expr
);
17294 -- Check for known value not multiple of alignment
17296 if No
(ACCR
.Y
) then
17297 if not Alignment_Checks_Suppressed
(ACCR
)
17298 and then X_Alignment
/= 0
17299 and then ACCR
.A
mod X_Alignment
/= 0
17302 ("??specified address for& is inconsistent with "
17303 & "alignment", ACCR
.N
, ACCR
.X
);
17305 ("\??program execution may be erroneous (RM 13.3(27))",
17308 Error_Msg_Uint_1
:= X_Alignment
;
17309 Error_Msg_NE
("\??alignment of & is ^", ACCR
.N
, ACCR
.X
);
17312 -- Check for large object overlaying smaller one
17314 elsif Y_Size
> Uint_0
17315 and then X_Size
> Uint_0
17316 and then X_Offs
+ X_Size
> Y_Size
17318 Error_Msg_NE
("??& overlays smaller object", ACCR
.N
, ACCR
.X
);
17320 ("\??program execution may be erroneous", ACCR
.N
);
17322 Error_Msg_Uint_1
:= X_Size
;
17323 Error_Msg_NE
("\??size of & is ^", ACCR
.N
, ACCR
.X
);
17325 Error_Msg_Uint_1
:= Y_Size
;
17326 Error_Msg_NE
("\??size of & is ^", ACCR
.N
, ACCR
.Y
);
17328 if Y_Size
>= X_Size
then
17329 Error_Msg_Uint_1
:= X_Offs
;
17330 Error_Msg_NE
("\??but offset of & is ^", ACCR
.N
, ACCR
.X
);
17333 -- Check for inadequate alignment, both of the base object
17334 -- and of the offset, if any. We only do this check if the
17335 -- run-time Alignment_Check is active. No point in warning
17336 -- if this check has been suppressed (or is suppressed by
17337 -- default in the non-strict alignment machine case).
17339 -- Note: we do not check the alignment if we gave a size
17340 -- warning, since it would likely be redundant.
17342 elsif not Alignment_Checks_Suppressed
(ACCR
)
17343 and then Y_Alignment
/= Uint_0
17345 (Y_Alignment
< X_Alignment
17348 and then Nkind
(Expr
) = N_Attribute_Reference
17349 and then Attribute_Name
(Expr
) = Name_Address
17350 and then Has_Compatible_Alignment
17351 (ACCR
.X
, Prefix
(Expr
), True) /=
17355 ("??specified address for& may be inconsistent with "
17356 & "alignment", ACCR
.N
, ACCR
.X
);
17358 ("\??program execution may be erroneous (RM 13.3(27))",
17361 Error_Msg_Uint_1
:= X_Alignment
;
17362 Error_Msg_NE
("\??alignment of & is ^", ACCR
.N
, ACCR
.X
);
17364 Error_Msg_Uint_1
:= Y_Alignment
;
17365 Error_Msg_NE
("\??alignment of & is ^", ACCR
.N
, ACCR
.Y
);
17367 if Y_Alignment
>= X_Alignment
then
17369 ("\??but offset is not multiple of alignment", ACCR
.N
);
17375 end Validate_Address_Clauses
;
17377 ------------------------------
17378 -- Validate_Iterable_Aspect --
17379 ------------------------------
17381 procedure Validate_Iterable_Aspect
(Typ
: Entity_Id
; ASN
: Node_Id
) is
17382 Aggr
: constant Node_Id
:= Expression
(ASN
);
17387 Cursor
: Entity_Id
;
17389 First_Id
: Entity_Id
:= Empty
;
17390 Last_Id
: Entity_Id
:= Empty
;
17391 Next_Id
: Entity_Id
:= Empty
;
17392 Has_Element_Id
: Entity_Id
:= Empty
;
17393 Element_Id
: Entity_Id
:= Empty
;
17396 if Nkind
(Aggr
) /= N_Aggregate
then
17397 Error_Msg_N
("aspect Iterable must be an aggregate", Aggr
);
17401 Cursor
:= Get_Cursor_Type
(ASN
, Typ
);
17403 -- If previous error aspect is unusable
17405 if Cursor
= Any_Type
then
17409 if not Is_Empty_List
(Expressions
(Aggr
)) then
17411 ("illegal positional association", First
(Expressions
(Aggr
)));
17414 -- Each expression must resolve to a function with the proper signature
17416 Assoc
:= First
(Component_Associations
(Aggr
));
17417 while Present
(Assoc
) loop
17418 Expr
:= Expression
(Assoc
);
17421 Prim
:= First
(Choices
(Assoc
));
17423 if Nkind
(Prim
) /= N_Identifier
or else Present
(Next
(Prim
)) then
17424 Error_Msg_N
("illegal name in association", Prim
);
17426 elsif Chars
(Prim
) = Name_First
then
17427 Resolve_Iterable_Operation
(Expr
, Cursor
, Typ
, Name_First
);
17428 First_Id
:= Entity
(Expr
);
17430 elsif Chars
(Prim
) = Name_Last
then
17431 Resolve_Iterable_Operation
(Expr
, Cursor
, Typ
, Name_Last
);
17432 Last_Id
:= Entity
(Expr
);
17434 elsif Chars
(Prim
) = Name_Previous
then
17435 Resolve_Iterable_Operation
(Expr
, Cursor
, Typ
, Name_Previous
);
17436 Last_Id
:= Entity
(Expr
);
17438 elsif Chars
(Prim
) = Name_Next
then
17439 Resolve_Iterable_Operation
(Expr
, Cursor
, Typ
, Name_Next
);
17440 Next_Id
:= Entity
(Expr
);
17442 elsif Chars
(Prim
) = Name_Has_Element
then
17443 Resolve_Iterable_Operation
(Expr
, Cursor
, Typ
, Name_Has_Element
);
17444 Has_Element_Id
:= Entity
(Expr
);
17446 elsif Chars
(Prim
) = Name_Element
then
17447 Resolve_Iterable_Operation
(Expr
, Cursor
, Typ
, Name_Element
);
17448 Element_Id
:= Entity
(Expr
);
17451 Error_Msg_N
("invalid name for iterable function", Prim
);
17457 if No
(First_Id
) then
17458 Error_Msg_N
("match for First primitive not found", ASN
);
17460 elsif No
(Next_Id
) then
17461 Error_Msg_N
("match for Next primitive not found", ASN
);
17463 elsif No
(Has_Element_Id
) then
17464 Error_Msg_N
("match for Has_Element primitive not found", ASN
);
17466 elsif No
(Element_Id
) or else No
(Last_Id
) then
17469 end Validate_Iterable_Aspect
;
17471 ------------------------------
17472 -- Validate_Literal_Aspect --
17473 ------------------------------
17475 procedure Validate_Literal_Aspect
(Typ
: Entity_Id
; ASN
: Node_Id
) is
17476 A_Id
: constant Aspect_Id
:= Get_Aspect_Id
(ASN
);
17477 pragma Assert
(A_Id
in Aspect_Integer_Literal |
17478 Aspect_Real_Literal | Aspect_String_Literal
);
17479 Func_Name
: constant Node_Id
:= Expression
(ASN
);
17480 Overloaded
: Boolean := Is_Overloaded
(Func_Name
);
17482 I
: Interp_Index
:= 0;
17484 Param_Type
: Entity_Id
;
17485 Match_Found
: Boolean := False;
17486 Match2_Found
: Boolean := False;
17487 Is_Match
: Boolean;
17489 Match2
: Entity_Id
:= Empty
;
17492 (Param_Id
: Entity_Id
; Param_Type
: Entity_Id
) return Boolean;
17493 -- Return True if Param_Id is a non aliased in parameter whose base type
17501 (Param_Id
: Entity_Id
; Param_Type
: Entity_Id
) return Boolean is
17503 return Base_Type
(Etype
(Param_Id
)) = Param_Type
17504 and then Ekind
(Param_Id
) = E_In_Parameter
17505 and then not Is_Aliased
(Param_Id
);
17509 if not Is_Type
(Typ
) then
17510 Error_Msg_N
("aspect can only be specified for a type", ASN
);
17513 elsif not Is_First_Subtype
(Typ
) then
17514 Error_Msg_N
("aspect cannot be specified for a subtype", ASN
);
17518 if A_Id
= Aspect_String_Literal
then
17519 if Is_String_Type
(Typ
) then
17520 Error_Msg_N
("aspect cannot be specified for a string type", ASN
);
17524 Param_Type
:= Standard_Wide_Wide_String
;
17527 if Is_Numeric_Type
(Typ
) then
17528 Error_Msg_N
("aspect cannot be specified for a numeric type", ASN
);
17532 Param_Type
:= Standard_String
;
17535 if not Overloaded
and then No
(Entity
(Func_Name
)) then
17536 -- The aspect is specified by a subprogram name, which
17537 -- may be an operator name given originally by a string.
17539 if Is_Operator_Name
(Chars
(Func_Name
)) then
17540 Analyze_Operator_Symbol
(Func_Name
);
17542 Analyze
(Func_Name
);
17545 Overloaded
:= Is_Overloaded
(Func_Name
);
17549 Get_First_Interp
(Func_Name
, I
=> I
, It
=> It
);
17551 -- only one possible interpretation
17552 It
.Nam
:= Entity
(Func_Name
);
17553 pragma Assert
(Present
(It
.Nam
));
17556 while It
.Nam
/= Empty
loop
17559 if Ekind
(It
.Nam
) = E_Function
17560 and then Base_Type
(Etype
(It
.Nam
)) = Base_Type
(Typ
)
17563 Params
: constant List_Id
:=
17564 Parameter_Specifications
(Parent
(It
.Nam
));
17565 Param_Spec
: Node_Id
;
17568 if List_Length
(Params
) = 1 then
17569 Param_Spec
:= First
(Params
);
17571 Matching
(Defining_Identifier
(Param_Spec
), Param_Type
);
17573 -- Look for the optional overloaded 2-param Real_Literal
17575 elsif List_Length
(Params
) = 2
17576 and then A_Id
= Aspect_Real_Literal
17578 Param_Spec
:= First
(Params
);
17580 if Matching
(Defining_Identifier
(Param_Spec
), Param_Type
)
17582 Param_Spec
:= Next
(Param_Spec
);
17584 if Matching
(Defining_Identifier
(Param_Spec
), Param_Type
)
17586 if No
(Match2
) then
17588 Match2_Found
:= True;
17590 -- If we find more than one possible match then
17591 -- do not take any into account here: since the
17592 -- 2-parameter version of Real_Literal is optional
17593 -- we cannot generate an error here, so let
17594 -- standard resolution fail later if we do need to
17595 -- call this variant.
17597 Match2_Found
:= False;
17606 if Match_Found
then
17607 Error_Msg_N
("aspect specification is ambiguous", ASN
);
17611 Match_Found
:= True;
17615 exit when not Overloaded
;
17617 if not Is_Match
then
17618 Remove_Interp
(I
=> I
);
17621 Get_Next_Interp
(I
=> I
, It
=> It
);
17624 if not Match_Found
then
17626 ("function name in aspect specification cannot be resolved", ASN
);
17630 Set_Entity
(Func_Name
, Match
.Nam
);
17631 Set_Etype
(Func_Name
, Etype
(Match
.Nam
));
17632 Set_Is_Overloaded
(Func_Name
, False);
17634 -- Record the match for 2-parameter function if found
17636 if Match2_Found
then
17637 Set_Related_Expression
(Match
.Nam
, Match2
);
17639 end Validate_Literal_Aspect
;
17641 ----------------------------------------
17642 -- Validate_Storage_Model_Type_Aspect --
17643 ----------------------------------------
17645 procedure Validate_Storage_Model_Type_Aspect
17646 (Typ
: Entity_Id
; ASN
: Node_Id
)
17649 Choice
: Entity_Id
;
17650 Choice_Name
: Name_Id
;
17653 Address_Type_Id
: Entity_Id
:= Empty
;
17654 Null_Address_Id
: Entity_Id
:= Empty
;
17655 Allocate_Id
: Entity_Id
:= Empty
;
17656 Deallocate_Id
: Entity_Id
:= Empty
;
17657 Copy_From_Id
: Entity_Id
:= Empty
;
17658 Copy_To_Id
: Entity_Id
:= Empty
;
17659 Storage_Size_Id
: Entity_Id
:= Empty
;
17661 procedure Check_And_Resolve_Storage_Model_Type_Argument
17664 Argument_Id
: in out Entity_Id
;
17666 -- Checks that the subaspect for Nam has not already been specified for
17667 -- Typ's Storage_Model_Type aspect (i.e., checks Argument_Id = Empty),
17668 -- resolves Expr, and sets Argument_Id to the entity resolved for Expr.
17670 procedure Check_And_Resolve_Storage_Model_Type_Argument
17673 Argument_Id
: in out Entity_Id
;
17676 Name_String
: String := Get_Name_String
(Nam
);
17679 To_Mixed
(Name_String
);
17681 if Present
(Argument_Id
) then
17682 Error_Msg_String
(1 .. Name_String
'Length) := Name_String
;
17683 Error_Msg_Strlen
:= Name_String
'Length;
17685 Error_Msg_N
("~ already specified", Expr
);
17688 Resolve_Storage_Model_Type_Argument
(Expr
, Typ
, Address_Type_Id
, Nam
);
17689 Argument_Id
:= Entity
(Expr
);
17690 end Check_And_Resolve_Storage_Model_Type_Argument
;
17692 -- Start of processing for Validate_Storage_Model_Type_Aspect
17695 -- The aggregate argument of Storage_Model_Type is optional, and when
17696 -- not present the aspect defaults to the native storage model (where
17697 -- the address type is System.Address, and other arguments default to
17698 -- the corresponding native storage operations).
17700 if No
(Expression
(ASN
)) then
17704 -- Each expression must resolve to an entity of the right kind or proper
17707 Assoc
:= First
(Component_Associations
(Expression
(ASN
)));
17708 while Present
(Assoc
) loop
17709 Expr
:= Expression
(Assoc
);
17712 Choice
:= First
(Choices
(Assoc
));
17714 Choice_Name
:= Chars
(Choice
);
17716 if Nkind
(Choice
) /= N_Identifier
or else Present
(Next
(Choice
)) then
17717 Error_Msg_N
("illegal name in association", Choice
);
17719 elsif Choice_Name
= Name_Address_Type
then
17720 if Assoc
/= First
(Component_Associations
(Expression
(ASN
))) then
17721 Error_Msg_N
("Address_Type must be first association", Choice
);
17724 Check_And_Resolve_Storage_Model_Type_Argument
17725 (Expr
, Typ
, Address_Type_Id
, Name_Address_Type
);
17728 -- It's allowed to leave out the Address_Type argument, in which
17729 -- case the address type is defined to default to System.Address.
17731 if No
(Address_Type_Id
) then
17732 Address_Type_Id
:= RTE
(RE_Address
);
17735 if Choice_Name
= Name_Null_Address
then
17736 Check_And_Resolve_Storage_Model_Type_Argument
17737 (Expr
, Typ
, Null_Address_Id
, Name_Null_Address
);
17739 elsif Choice_Name
= Name_Allocate
then
17740 Check_And_Resolve_Storage_Model_Type_Argument
17741 (Expr
, Typ
, Allocate_Id
, Name_Allocate
);
17743 elsif Choice_Name
= Name_Deallocate
then
17744 Check_And_Resolve_Storage_Model_Type_Argument
17745 (Expr
, Typ
, Deallocate_Id
, Name_Deallocate
);
17747 elsif Choice_Name
= Name_Copy_From
then
17748 Check_And_Resolve_Storage_Model_Type_Argument
17749 (Expr
, Typ
, Copy_From_Id
, Name_Copy_From
);
17751 elsif Choice_Name
= Name_Copy_To
then
17752 Check_And_Resolve_Storage_Model_Type_Argument
17753 (Expr
, Typ
, Copy_To_Id
, Name_Copy_To
);
17755 elsif Choice_Name
= Name_Storage_Size
then
17756 Check_And_Resolve_Storage_Model_Type_Argument
17757 (Expr
, Typ
, Storage_Size_Id
, Name_Storage_Size
);
17761 ("invalid name for Storage_Model_Type argument", Choice
);
17768 -- If Address_Type has been specified as or defaults to System.Address,
17769 -- then other "subaspect" arguments can be specified, but are optional.
17770 -- Otherwise, all other arguments are required and an error is flagged
17771 -- about any that are missing.
17773 if Address_Type_Id
= RTE
(RE_Address
) then
17776 elsif No
(Null_Address_Id
) then
17777 Error_Msg_N
("match for Null_Address primitive not found", ASN
);
17779 elsif No
(Allocate_Id
) then
17780 Error_Msg_N
("match for Allocate primitive not found", ASN
);
17782 elsif No
(Deallocate_Id
) then
17783 Error_Msg_N
("match for Deallocate primitive not found", ASN
);
17785 elsif No
(Copy_From_Id
) then
17786 Error_Msg_N
("match for Copy_From primitive not found", ASN
);
17788 elsif No
(Copy_To_Id
) then
17789 Error_Msg_N
("match for Copy_To primitive not found", ASN
);
17791 elsif No
(Storage_Size_Id
) then
17792 Error_Msg_N
("match for Storage_Size primitive not found", ASN
);
17794 end Validate_Storage_Model_Type_Aspect
;
17796 -----------------------------------
17797 -- Validate_Unchecked_Conversion --
17798 -----------------------------------
17800 procedure Validate_Unchecked_Conversion
17802 Act_Unit
: Entity_Id
)
17804 Source
: Entity_Id
;
17805 Target
: Entity_Id
;
17807 procedure Warn_Nonportable
(RE
: RE_Id
);
17808 -- Warn if either source or target of the conversion is a predefined
17809 -- private type, whose representation might differ between releases and
17810 -- targets of the compiler.
17812 ----------------------
17813 -- Warn_Nonportable --
17814 ----------------------
17816 procedure Warn_Nonportable
(RE
: RE_Id
) is
17818 if Is_RTE
(Source
, RE
) or else Is_RTE
(Target
, RE
) then
17819 pragma Assert
(Is_Private_Type
(RTE
(RE
)));
17821 ("?z?representation of & values may change between "
17822 & "'G'N'A'T versions", N
, RTE
(RE
));
17824 end Warn_Nonportable
;
17830 -- Start of processing for Validate_Unchecked_Conversion
17833 -- Obtain source and target types. Note that we call Ancestor_Subtype
17834 -- here because the processing for generic instantiation always makes
17835 -- subtypes, and we want the original frozen actual types.
17837 Source
:= Ancestor_Subtype
(Etype
(First_Formal
(Act_Unit
)));
17838 Target
:= Ancestor_Subtype
(Etype
(Act_Unit
));
17840 -- If either type is generic, the instantiation happens within a generic
17841 -- unit, and there is nothing to check. The proper check will happen
17842 -- when the enclosing generic is instantiated.
17844 if Is_Generic_Type
(Source
) or else Is_Generic_Type
(Target
) then
17848 -- Warn if one of the operands is a private type declared in
17849 -- Ada.Calendar or Ada.Real_Time. Do not emit a warning when compiling
17850 -- GNAT-related sources.
17852 if Warn_On_Unchecked_Conversion
17853 and then not In_Predefined_Unit
(N
)
17855 Warn_Nonportable
(RO_CA_Time
);
17856 Warn_Nonportable
(RO_RT_Time
);
17857 Warn_Nonportable
(RE_Time_Span
);
17860 -- If we are dealing with private types, then do the check on their
17861 -- fully declared counterparts if the full declarations have been
17862 -- encountered (they don't have to be visible, but they must exist).
17864 if Is_Private_Type
(Source
)
17865 and then Present
(Underlying_Type
(Source
))
17867 Source
:= Underlying_Type
(Source
);
17870 if Is_Private_Type
(Target
)
17871 and then Present
(Underlying_Type
(Target
))
17873 Target
:= Underlying_Type
(Target
);
17876 -- Source may be unconstrained array, but not target, except in relaxed
17879 if Is_Array_Type
(Target
)
17880 and then not Is_Constrained
(Target
)
17881 and then not Relaxed_RM_Semantics
17884 ("unchecked conversion to unconstrained array not allowed", N
);
17888 -- Warn if conversion between two different convention pointers
17890 if Is_Access_Type
(Target
)
17891 and then Is_Access_Type
(Source
)
17892 and then Convention
(Target
) /= Convention
(Source
)
17893 and then Warn_On_Unchecked_Conversion
17895 -- Give warnings for subprogram pointers only on most targets
17897 if Is_Access_Subprogram_Type
(Target
)
17898 or else Is_Access_Subprogram_Type
(Source
)
17901 ("?z?conversion between pointers with different conventions!",
17906 -- Make entry in unchecked conversion table for later processing by
17907 -- Validate_Unchecked_Conversions, which will check sizes and alignments
17908 -- (using values set by the back end where possible). This is only done
17909 -- if the appropriate warning is active.
17911 if Warn_On_Unchecked_Conversion
then
17912 Unchecked_Conversions
.Append
17913 (New_Val
=> UC_Entry
'(Eloc => Sloc (N),
17916 Act_Unit => Act_Unit));
17918 -- If both sizes are known statically now, then back-end annotation
17919 -- is not required to do a proper check but if either size is not
17920 -- known statically, then we need the annotation.
17922 if Known_Static_RM_Size (Source)
17924 Known_Static_RM_Size (Target)
17928 Back_Annotate_Rep_Info := True;
17932 -- If unchecked conversion to access type, and access type is declared
17933 -- in the same unit as the unchecked conversion, then set the flag
17934 -- No_Strict_Aliasing (no strict aliasing is implicit here)
17936 if Is_Access_Type (Target)
17937 and then In_Same_Source_Unit (Target, N)
17939 Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
17942 -- If the unchecked conversion is between Address and an access
17943 -- subprogram type, show that we shouldn't use an internal
17944 -- representation for the access subprogram type.
17946 if Is_Access_Subprogram_Type (Target)
17947 and then Is_Descendant_Of_Address (Source)
17948 and then In_Same_Source_Unit (Target, N)
17950 Set_Can_Use_Internal_Rep (Base_Type (Target), False);
17951 elsif Is_Access_Subprogram_Type (Source)
17952 and then Is_Descendant_Of_Address (Target)
17953 and then In_Same_Source_Unit (Source, N)
17955 Set_Can_Use_Internal_Rep (Base_Type (Source), False);
17958 -- Generate N_Validate_Unchecked_Conversion node for back end in case
17959 -- the back end needs to perform special validation checks.
17961 -- Shouldn't this be in Exp_Ch13, since the check only gets done if we
17962 -- have full expansion and the back end is called ???
17965 Make_Validate_Unchecked_Conversion (Sloc (N));
17966 Set_Source_Type (Vnode, Source);
17967 Set_Target_Type (Vnode, Target);
17969 -- If the unchecked conversion node is in a list, just insert before it.
17970 -- If not we have some strange case, not worth bothering about.
17972 if Is_List_Member (N) then
17973 Insert_After (N, Vnode);
17975 end Validate_Unchecked_Conversion;
17977 ------------------------------------
17978 -- Validate_Unchecked_Conversions --
17979 ------------------------------------
17981 procedure Validate_Unchecked_Conversions is
17982 function Is_Null_Array (T : Entity_Id) return Boolean;
17983 -- We want to warn in the case of converting to a wrong-sized array of
17984 -- bytes, including the zero-size case. This returns True in that case,
17985 -- which is necessary because a size of 0 is used to indicate both an
17986 -- unknown size and a size of 0. It's OK for this to return True in
17987 -- other zero-size cases, but we don't go out of our way; for example,
17988 -- we don't bother with multidimensional arrays.
17990 function Is_Null_Array (T : Entity_Id) return Boolean is
17992 if Is_Array_Type (T) and then Is_Constrained (T) then
17994 Index : constant Node_Id := First_Index (T);
17995 R : Node_Id; -- N_Range
17997 case Nkind (Index) is
18000 when N_Subtype_Indication =>
18001 R := Range_Expression (Constraint (Index));
18002 when N_Identifier | N_Expanded_Name =>
18003 R := Scalar_Range (Entity (Index));
18005 raise Program_Error;
18008 return Is_Null_Range (Low_Bound (R), High_Bound (R));
18016 for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
18018 T : UC_Entry renames Unchecked_Conversions.Table (N);
18020 Act_Unit : constant Entity_Id := T.Act_Unit;
18021 Eloc : constant Source_Ptr := T.Eloc;
18022 Source : constant Entity_Id := T.Source;
18023 Target : constant Entity_Id := T.Target;
18029 -- Skip if function marked as warnings off
18031 if Has_Warnings_Off (Act_Unit)
18032 or else Serious_Errors_Detected > 0
18037 -- Don't do the check if warnings off for either type, note the
18038 -- deliberate use of OR here instead of OR ELSE to get the flag
18039 -- Warnings_Off_Used set for both types if appropriate.
18041 if Has_Warnings_Off (Source) or Has_Warnings_Off (Target) then
18045 if (Known_Static_RM_Size (Source)
18046 and then Known_Static_RM_Size (Target))
18047 or else Is_Null_Array (Target)
18049 -- This validation check, which warns if we have unequal sizes
18050 -- for unchecked conversion, and thus implementation dependent
18051 -- semantics, is one of the few occasions on which we use the
18052 -- official RM size instead of Esize. See description in Einfo
18053 -- "Handling of Type'Size Values" for details.
18055 Source_Siz := RM_Size (Source);
18056 Target_Siz := RM_Size (Target);
18058 if Present (Source_Siz) and then Present (Target_Siz)
18059 and then Source_Siz /= Target_Siz
18062 ("?z?types for unchecked conversion have different sizes!",
18065 if All_Errors_Mode then
18066 Error_Msg_Name_1 := Chars (Source);
18067 Error_Msg_Uint_1 := Source_Siz;
18068 Error_Msg_Name_2 := Chars (Target);
18069 Error_Msg_Uint_2 := Target_Siz;
18070 Error_Msg ("\size of % is ^, size of % is ^?z?", Eloc);
18072 Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
18074 if Is_Discrete_Type (Source)
18076 Is_Discrete_Type (Target)
18078 if Source_Siz > Target_Siz then
18080 ("\?z?^ high order bits of source will "
18081 & "be ignored!", Eloc);
18083 elsif Is_Unsigned_Type (Source) then
18085 ("\?z?source will be extended with ^ high order "
18086 & "zero bits!", Eloc);
18090 ("\?z?source will be extended with ^ high order "
18091 & "sign bits!", Eloc);
18094 elsif Source_Siz < Target_Siz then
18095 if Is_Discrete_Type (Target) then
18096 if Bytes_Big_Endian then
18098 ("\?z?target value will include ^ undefined "
18099 & "low order bits!", Eloc, Act_Unit);
18102 ("\?z?target value will include ^ undefined "
18103 & "high order bits!", Eloc, Act_Unit);
18108 ("\?z?^ trailing bits of target value will be "
18109 & "undefined!", Eloc, Act_Unit);
18112 else pragma Assert (Source_Siz > Target_Siz);
18113 if Is_Discrete_Type (Source) then
18114 if Bytes_Big_Endian then
18116 ("\?z?^ low order bits of source will be "
18117 & "ignored!", Eloc, Act_Unit);
18120 ("\?z?^ high order bits of source will be "
18121 & "ignored!", Eloc, Act_Unit);
18126 ("\?z?^ trailing bits of source will be "
18127 & "ignored!", Eloc, Act_Unit);
18134 -- If both types are access types, we need to check the alignment.
18135 -- If the alignment of both is specified, we can do it here.
18137 if Serious_Errors_Detected = 0
18138 and then Is_Access_Type (Source)
18139 and then Is_Access_Type (Target)
18140 and then Target_Strict_Alignment
18141 and then Present (Designated_Type (Source))
18142 and then Present (Designated_Type (Target))
18145 D_Source : constant Entity_Id := Designated_Type (Source);
18146 D_Target : constant Entity_Id := Designated_Type (Target);
18149 if Known_Alignment (D_Source)
18151 Known_Alignment (D_Target)
18154 Source_Align : constant Uint := Alignment (D_Source);
18155 Target_Align : constant Uint := Alignment (D_Target);
18158 if Source_Align < Target_Align
18159 and then not Is_Tagged_Type (D_Source)
18161 -- Suppress warning if warnings suppressed on either
18162 -- type or either designated type. Note the use of
18163 -- OR here instead of OR ELSE. That is intentional,
18164 -- we would like to set flag Warnings_Off_Used in
18165 -- all types for which warnings are suppressed.
18167 and then not (Has_Warnings_Off (D_Source)
18169 Has_Warnings_Off (D_Target)
18171 Has_Warnings_Off (Source)
18173 Has_Warnings_Off (Target))
18175 Error_Msg_Uint_1 := Target_Align;
18176 Error_Msg_Uint_2 := Source_Align;
18177 Error_Msg_Node_1 := D_Target;
18178 Error_Msg_Node_2 := D_Source;
18180 ("?z?alignment of & (^) is stricter than "
18181 & "alignment of & (^)!", Eloc, Act_Unit);
18183 ("\?z?resulting access value may have invalid "
18184 & "alignment!", Eloc, Act_Unit);
18195 end Validate_Unchecked_Conversions;