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 Analyze_User_Aspect_Aspect_Specification
(N
: Node_Id
);
112 -- Analyze a User_Aspect aspect specification. Called from outside
113 -- this package (in addition to locally), but the call from aspect.adb
114 -- is via an access-to-subprogram value.
116 procedure Build_Discrete_Static_Predicate
120 -- Given a predicated type Typ, where Typ is a discrete static subtype,
121 -- whose predicate expression is Expr, tests if Expr is a static predicate,
122 -- and if so, builds the predicate range list. Nam is the name of the one
123 -- argument to the predicate function. Occurrences of the type name in the
124 -- predicate expression have been replaced by identifier references to this
125 -- name, which is unique, so any identifier with Chars matching Nam must be
126 -- a reference to the type. If the predicate is non-static, this procedure
127 -- returns doing nothing. If the predicate is static, then the predicate
128 -- list is stored in Static_Discrete_Predicate (Typ), and the Expr is
129 -- rewritten as a canonicalized membership operation.
131 function Build_Export_Import_Pragma
133 Id
: Entity_Id
) return Node_Id
;
134 -- Create the corresponding pragma for aspect Export or Import denoted by
135 -- Asp. Id is the related entity subject to the aspect. Return Empty when
136 -- the expression of aspect Asp evaluates to False or is erroneous.
138 function Build_Predicate_Function_Declaration
139 (Typ
: Entity_Id
) return Node_Id
;
140 -- Build the declaration for a predicate function. The declaration is built
141 -- at the same time as the body but inserted before, as explained below.
143 procedure Build_Predicate_Function
(Typ
: Entity_Id
; N
: Node_Id
);
144 -- If Typ has predicates (indicated by Has_Predicates being set for Typ),
145 -- then either there are pragma Predicate entries on the rep chain for the
146 -- type (note that Predicate aspects are converted to pragma Predicate), or
147 -- there are inherited aspects from a parent type, or ancestor subtypes.
148 -- This procedure builds body for the Predicate function that tests these
149 -- predicates. N is the freeze node for the type. The spec of the function
150 -- is inserted before the freeze node, and the body of the function is
151 -- inserted after the freeze node.
153 procedure Check_Pool_Size_Clash
(Ent
: Entity_Id
; SP
, SS
: Node_Id
);
154 -- Called if both Storage_Pool and Storage_Size attribute definition
155 -- clauses (SP and SS) are present for entity Ent. Issue error message.
157 procedure Freeze_Entity_Checks
(N
: Node_Id
);
158 -- Called from Analyze_Freeze_Entity and Analyze_Generic_Freeze Entity
159 -- to generate appropriate semantic checks that are delayed until this
160 -- point (they had to be delayed this long for cases of delayed aspects,
161 -- e.g. analysis of statically predicated subtypes in choices, for which
162 -- we have to be sure the subtypes in question are frozen before checking).
164 function Get_Alignment_Value
(Expr
: Node_Id
) return Uint
;
165 -- Given the expression for an alignment value, returns the corresponding
166 -- Uint value. If the value is inappropriate, then error messages are
167 -- posted as required, and a value of No_Uint is returned.
169 function Is_Operational_Item
(N
: Node_Id
) return Boolean;
170 -- A specification for a stream attribute is allowed before the full type
171 -- is declared, as explained in AI-00137 and the corrigendum. Attributes
172 -- that do not specify a representation characteristic are operational
175 function Is_Static_Choice
(N
: Node_Id
) return Boolean;
176 -- Returns True if N represents a static choice (static subtype, or
177 -- static subtype indication, or static expression, or static range).
179 -- Note that this is a bit more inclusive than we actually need
180 -- (in particular membership tests do not allow the use of subtype
181 -- indications). But that doesn't matter, we have already checked
182 -- that the construct is legal to get this far.
184 function Is_Type_Related_Rep_Item
(N
: Node_Id
) return Boolean;
185 -- Returns True for a representation clause/pragma that specifies a
186 -- type-related representation (as opposed to operational) aspect.
188 function Is_Predicate_Static
191 Warn
: Boolean := True) return Boolean;
192 -- Given predicate expression Expr, tests if Expr is predicate-static in
193 -- the sense of the rules in (RM 3.2.4 (15-24)). Occurrences of the type
194 -- name in the predicate expression have been replaced by references to
195 -- an identifier whose Chars field is Nam. This name is unique, so any
196 -- identifier with Chars matching Nam must be a reference to the type.
197 -- Returns True if the expression is predicate-static and False otherwise,
198 -- but is not in the business of setting flags or issuing error messages.
200 -- Only scalar types can have static predicates, so False is always
201 -- returned for non-scalar types.
203 -- Note: the RM seems to suggest that string types can also have static
204 -- predicates. But that really makes little sense as very few useful
205 -- predicates can be constructed for strings. Remember that:
209 -- is not a static expression. So even though the clearly faulty RM wording
210 -- allows the following:
212 -- subtype S is String with Static_Predicate => S < "DEF"
214 -- We can't allow this, otherwise we have predicate-static applying to a
215 -- larger class than static expressions, which was never intended.
217 -- The Warn parameter is True iff this is not a recursive call. This
218 -- parameter is used to avoid generating warnings for subexpressions and
219 -- for cases where the predicate expression (as originally written by
220 -- the user, before any transformations) is a Boolean literal.
222 procedure New_Put_Image_Subprogram
226 -- Similar to New_Stream_Subprogram, but for the Put_Image attribute
228 procedure New_Stream_Subprogram
232 Nam
: TSS_Name_Type
);
233 -- Create a subprogram renaming of a given stream attribute to the
234 -- designated subprogram and then in the tagged case, provide this as a
235 -- primitive operation, or in the untagged case make an appropriate TSS
236 -- entry. This is more properly an expansion activity than just semantics,
237 -- but the presence of user-defined stream functions for limited types
238 -- is a legality check, which is why this takes place here rather than in
239 -- exp_ch13, where it was previously. Nam indicates the name of the TSS
240 -- function to be generated.
242 -- To avoid elaboration anomalies with freeze nodes, for untagged types
243 -- we generate both a subprogram declaration and a subprogram renaming
244 -- declaration, so that the attribute specification is handled as a
245 -- renaming_as_body. For tagged types, the specification is one of the
248 procedure No_Type_Rep_Item
(N
: Node_Id
);
249 -- Output message indicating that no type-related aspects can be
250 -- specified due to some property of the parent type.
252 procedure Register_Address_Clause_Check
258 -- Register a check for the address clause N. The rest of the parameters
259 -- are in keeping with the components of Address_Clause_Check_Record below.
261 procedure Validate_Aspect_Aggregate
(N
: Node_Id
);
262 -- Check legality of operations given in the Ada 2022 Aggregate aspect for
265 procedure Resolve_Aspect_Aggregate
268 -- Resolve each one of the operations specified in the specification of
271 procedure Validate_Aspect_Local_Restrictions
(E
: Entity_Id
; N
: Node_Id
);
272 -- Check legality of a Local_Restrictions aspect specification
274 procedure Validate_Aspect_Stable_Properties
275 (E
: Entity_Id
; N
: Node_Id
; Class_Present
: Boolean);
276 -- Check legality of functions given in the Ada 2022 Stable_Properties
277 -- (or Stable_Properties'Class) aspect.
279 procedure Validate_Storage_Model_Type_Aspect
280 (Typ
: Entity_Id
; ASN
: Node_Id
);
281 -- Check legality and completeness of the aggregate associations given in
282 -- the Storage_Model_Type aspect associated with Typ.
284 procedure Resolve_Storage_Model_Type_Argument
287 Addr_Type
: in out Entity_Id
;
289 -- Resolve argument N to be of the proper kind (when a type or constant)
290 -- or to have the proper profile (when a subprogram).
292 procedure Resolve_Aspect_Stable_Properties
293 (Typ_Or_Subp
: Entity_Id
;
295 Class_Present
: Boolean);
296 -- Resolve each one of the functions specified in the specification of
297 -- aspect Stable_Properties (or Stable_Properties'Class).
299 procedure Resolve_Iterable_Operation
304 -- If the name of a primitive operation for an Iterable aspect is
305 -- overloaded, resolve according to required signature.
311 Biased
: Boolean := True);
312 -- If Biased is True, sets Has_Biased_Representation flag for E, and
313 -- outputs a warning message at node N if Warn_On_Biased_Representation is
314 -- is True. This warning inserts the string Msg to describe the construct
317 -----------------------------------------------------------
318 -- Visibility of Discriminants in Aspect Specifications --
319 -----------------------------------------------------------
321 -- The discriminants of a type are visible when analyzing the aspect
322 -- specifications of a type declaration or protected type declaration,
323 -- but not when analyzing those of a subtype declaration. The following
324 -- routines enforce this distinction.
326 procedure Push_Type
(E
: Entity_Id
);
327 -- Push scope E and make visible the discriminants of type entity E if E
328 -- has discriminants and is not a subtype.
330 procedure Pop_Type
(E
: Entity_Id
);
331 -- Remove visibility to the discriminants of type entity E and pop the
332 -- scope stack if E has discriminants and is not a subtype.
334 ----------------------------------------------
335 -- Table for Validate_Unchecked_Conversions --
336 ----------------------------------------------
338 -- The following table collects unchecked conversions for validation.
339 -- Entries are made by Validate_Unchecked_Conversion and then the call
340 -- to Validate_Unchecked_Conversions does the actual error checking and
341 -- posting of warnings. The reason for this delayed processing is to take
342 -- advantage of back-annotations of size and alignment values performed by
345 -- Note: the reason we store a Source_Ptr value instead of a Node_Id is
346 -- that by the time Validate_Unchecked_Conversions is called, Sprint will
347 -- already have modified all Sloc values if the -gnatD option is set.
349 type UC_Entry
is record
350 Eloc
: Source_Ptr
; -- node used for posting warnings
351 Source
: Entity_Id
; -- source type for unchecked conversion
352 Target
: Entity_Id
; -- target type for unchecked conversion
353 Act_Unit
: Entity_Id
; -- actual function instantiated
356 package Unchecked_Conversions
is new Table
.Table
(
357 Table_Component_Type
=> UC_Entry
,
358 Table_Index_Type
=> Int
,
359 Table_Low_Bound
=> 1,
361 Table_Increment
=> 200,
362 Table_Name
=> "Unchecked_Conversions");
364 ----------------------------------------
365 -- Table for Validate_Address_Clauses --
366 ----------------------------------------
368 -- If an address clause has the form
370 -- for X'Address use Expr
372 -- where Expr has a value known at compile time or is of the form Y'Address
373 -- or recursively is a reference to a constant initialized with either of
374 -- these forms, and the value of Expr is not a multiple of X's alignment,
375 -- or if Y has a smaller alignment than X, then that merits a warning about
376 -- possible bad alignment. The following table collects address clauses of
377 -- this kind. We put these in a table so that they can be checked after the
378 -- back end has completed annotation of the alignments of objects, since we
379 -- can catch more cases that way.
381 type Address_Clause_Check_Record
is record
383 -- The address clause
386 -- The entity of the object subject to the address clause
389 -- The value of the address in the first case
392 -- The entity of the object being overlaid in the second case
395 -- Whether the address is offset within Y in the second case
397 Alignment_Checks_Suppressed
: Boolean;
398 -- Whether alignment checks are suppressed by an active scope suppress
399 -- setting. We need to save the value in order to be able to reuse it
400 -- after the back end has been run.
403 package Address_Clause_Checks
is new Table
.Table
(
404 Table_Component_Type
=> Address_Clause_Check_Record
,
405 Table_Index_Type
=> Int
,
406 Table_Low_Bound
=> 1,
408 Table_Increment
=> 200,
409 Table_Name
=> "Address_Clause_Checks");
411 function Alignment_Checks_Suppressed
412 (ACCR
: Address_Clause_Check_Record
) return Boolean;
413 -- Return whether the alignment check generated for the address clause
416 ---------------------------------
417 -- Alignment_Checks_Suppressed --
418 ---------------------------------
420 function Alignment_Checks_Suppressed
421 (ACCR
: Address_Clause_Check_Record
) return Boolean
424 if Checks_May_Be_Suppressed
(ACCR
.X
) then
425 return Is_Check_Suppressed
(ACCR
.X
, Alignment_Check
);
427 return ACCR
.Alignment_Checks_Suppressed
;
429 end Alignment_Checks_Suppressed
;
431 -----------------------------------------
432 -- Adjust_Record_For_Reverse_Bit_Order --
433 -----------------------------------------
435 procedure Adjust_Record_For_Reverse_Bit_Order
(R
: Entity_Id
) is
436 Max_Machine_Scalar_Size
: constant Uint
:=
437 UI_From_Int
(if Reverse_Bit_Order_Threshold
>= 0
438 then Reverse_Bit_Order_Threshold
439 else System_Max_Integer_Size
);
440 -- We use this as the maximum machine scalar size
442 SSU
: constant Uint
:= UI_From_Int
(System_Storage_Unit
);
449 -- The processing done here used to depend on the Ada version, but the
450 -- behavior has been changed by AI95-0133. However this AI is a Binding
451 -- Interpretation, so we now implement it even in Ada 95 mode. But the
452 -- original behavior from unamended Ada 95 is available for the sake of
453 -- compatibility under the debugging switch -gnatd.p in Ada 95 mode.
455 if Ada_Version
< Ada_2005
and then Debug_Flag_Dot_P
then
456 Adjust_Record_For_Reverse_Bit_Order_Ada_95
(R
);
460 -- For Ada 2005, we do machine scalar processing, as fully described In
461 -- AI-133. This involves gathering all components which start at the
462 -- same byte offset and processing them together. Same approach is still
463 -- valid in later versions including Ada 2012.
465 -- Note that component clauses found on record types may be inherited,
466 -- in which case the layout of the component with such a clause still
467 -- has to be done at this point. Therefore, the processing done here
468 -- must exclusively rely on the Component_Clause of the component.
470 -- This first loop through components does two things. First it deals
471 -- with the case of components with component clauses whose length is
472 -- greater than the maximum machine scalar size (either accepting them
473 -- or rejecting as needed). Second, it counts the number of components
474 -- with component clauses whose length does not exceed this maximum for
478 Comp
:= First_Component_Or_Discriminant
(R
);
479 while Present
(Comp
) loop
480 CC
:= Component_Clause
(Comp
);
484 Fbit
: constant Uint
:= Static_Integer
(First_Bit
(CC
));
485 Lbit
: constant Uint
:= Static_Integer
(Last_Bit
(CC
));
488 -- Case of component with last bit >= max machine scalar
490 if Lbit
>= Max_Machine_Scalar_Size
then
492 -- This is allowed only if first bit is zero, and last bit
493 -- + 1 is a multiple of storage unit size.
495 if Fbit
= 0 and then (Lbit
+ 1) mod SSU
= 0 then
497 -- This is the case to give a warning if enabled
499 if Warn_On_Reverse_Bit_Order
then
501 ("info: multi-byte field specified with "
502 & "non-standard Bit_Order?.v?", CC
);
504 if Bytes_Big_Endian
then
506 ("\bytes are not reversed "
507 & "(component is big-endian)?.v?", CC
);
510 ("\bytes are not reversed "
511 & "(component is little-endian)?.v?", CC
);
515 -- Give error message for RM 13.5.1(10) violation
519 ("machine scalar rules not followed for&",
520 First_Bit
(CC
), Comp
);
522 Error_Msg_Uint_1
:= Lbit
+ 1;
523 Error_Msg_Uint_2
:= Max_Machine_Scalar_Size
;
525 ("\last bit + 1 (^) exceeds maximum machine scalar "
526 & "size (^)", First_Bit
(CC
));
528 if (Lbit
+ 1) mod SSU
/= 0 then
529 Error_Msg_Uint_1
:= SSU
;
531 ("\and is not a multiple of Storage_Unit (^) "
532 & "(RM 13.5.1(10))", First_Bit
(CC
));
535 Error_Msg_Uint_1
:= Fbit
;
537 ("\and first bit (^) is non-zero "
538 & "(RM 13.4.1(10))", First_Bit
(CC
));
542 -- OK case of machine scalar related component clause. For now,
546 Num_CC
:= Num_CC
+ 1;
551 Next_Component_Or_Discriminant
(Comp
);
554 -- We need to sort the component clauses on the basis of the Position
555 -- values in the clause, so we can group clauses with the same Position
556 -- together to determine the relevant machine scalar size.
559 Comps
: array (0 .. Num_CC
) of Entity_Id
;
560 -- Array to collect component and discriminant entities. The data
561 -- starts at index 1, the 0'th entry is for the sort routine.
563 function CP_Lt
(Op1
, Op2
: Natural) return Boolean;
564 -- Compare routine for Sort
566 procedure CP_Move
(From
: Natural; To
: Natural);
567 -- Move routine for Sort
569 package Sorting
is new GNAT
.Heap_Sort_G
(CP_Move
, CP_Lt
);
572 -- Maximum last bit value of any component in this set
575 -- Corresponding machine scalar size
579 -- Start and stop positions in the component list of the set of
580 -- components with the same starting position (that constitute
581 -- components in a single machine scalar).
587 function CP_Lt
(Op1
, Op2
: Natural) return Boolean is
590 Position
(Component_Clause
(Comps
(Op1
))) <
591 Position
(Component_Clause
(Comps
(Op2
)));
598 procedure CP_Move
(From
: Natural; To
: Natural) is
600 Comps
(To
) := Comps
(From
);
603 -- Start of processing for Sort_CC
606 -- Collect the machine scalar relevant component clauses
609 Comp
:= First_Component_Or_Discriminant
(R
);
610 while Present
(Comp
) loop
612 CC
: constant Node_Id
:= Component_Clause
(Comp
);
615 -- Collect only component clauses whose last bit is less than
616 -- machine scalar size. Any component clause whose last bit
617 -- exceeds this value does not take part in machine scalar
618 -- layout considerations. The test for Error_Posted makes sure
619 -- we exclude component clauses for which we already posted an
623 and then not Error_Posted
(Last_Bit
(CC
))
624 and then Static_Integer
(Last_Bit
(CC
)) <
625 Max_Machine_Scalar_Size
627 Num_CC
:= Num_CC
+ 1;
628 Comps
(Num_CC
) := Comp
;
632 Next_Component_Or_Discriminant
(Comp
);
635 -- Sort by ascending position number
637 Sorting
.Sort
(Num_CC
);
639 -- We now have all the components whose size does not exceed the max
640 -- machine scalar value, sorted by starting position. In this loop we
641 -- gather groups of clauses starting at the same position, to process
642 -- them in accordance with AI-133.
645 while Stop
< Num_CC
loop
650 (Last_Bit
(Component_Clause
(Comps
(Start
))));
651 while Stop
< Num_CC
loop
653 (Position
(Component_Clause
(Comps
(Stop
+ 1)))) =
655 (Position
(Component_Clause
(Comps
(Stop
))))
663 (Component_Clause
(Comps
(Stop
)))));
669 -- Now we have a group of component clauses from Start to Stop
670 -- whose positions are identical, and MaxL is the maximum last
671 -- bit value of any of these components.
673 -- We need to determine the corresponding machine scalar size.
674 -- This loop assumes that machine scalar sizes are even, and that
675 -- each possible machine scalar has twice as many bits as the next
678 MSS
:= Max_Machine_Scalar_Size
;
680 and then (MSS
/ 2) >= SSU
681 and then (MSS
/ 2) > MaxL
686 -- Here is where we fix up the Component_Bit_Offset value to
687 -- account for the reverse bit order. Some examples of what needs
688 -- to be done for the case of a machine scalar size of 8 are:
690 -- First_Bit .. Last_Bit Component_Bit_Offset
702 -- The rule is that the first bit is obtained by subtracting the
703 -- old ending bit from machine scalar size - 1.
705 for C
in Start
.. Stop
loop
707 Comp
: constant Entity_Id
:= Comps
(C
);
708 CC
: constant Node_Id
:= Component_Clause
(Comp
);
710 FB
: constant Uint
:= Static_Integer
(First_Bit
(CC
));
711 LB
: constant Uint
:= Static_Integer
(Last_Bit
(CC
));
712 NFB
: constant Uint
:= MSS
- 1 - LB
;
713 NLB
: constant Uint
:= NFB
+ LB
- FB
;
714 Pos
: constant Uint
:= Static_Integer
(Position
(CC
));
717 -- Do not warn for the artificial clause built for the tag
718 -- in Check_Record_Representation_Clause if it is inherited.
720 if Warn_On_Reverse_Bit_Order
721 and then Chars
(Comp
) /= Name_uTag
723 Error_Msg_Uint_1
:= MSS
;
725 ("info: reverse bit order in machine scalar of "
726 & "length^?.v?", First_Bit
(CC
));
727 Error_Msg_Uint_1
:= NFB
;
728 Error_Msg_Uint_2
:= NLB
;
730 if Bytes_Big_Endian
then
732 ("\big-endian range for component & is ^ .. ^?.v?",
733 First_Bit
(CC
), Comp
);
736 ("\little-endian range for component " &
738 First_Bit
(CC
), Comp
);
742 Set_Component_Bit_Offset
(Comp
, Pos
* SSU
+ NFB
);
743 Set_Esize
(Comp
, 1 + (NLB
- NFB
));
744 Set_Normalized_First_Bit
(Comp
, NFB
mod SSU
);
745 Set_Normalized_Position
(Comp
, Pos
+ NFB
/ SSU
);
750 end Adjust_Record_For_Reverse_Bit_Order
;
752 ------------------------------------------------
753 -- Adjust_Record_For_Reverse_Bit_Order_Ada_95 --
754 ------------------------------------------------
756 procedure Adjust_Record_For_Reverse_Bit_Order_Ada_95
(R
: Entity_Id
) is
761 -- For Ada 95, we just renumber bits within a storage unit. We do the
762 -- same for Ada 83 mode, since we recognize the Bit_Order attribute in
763 -- Ada 83, and are free to add this extension.
765 Comp
:= First_Component_Or_Discriminant
(R
);
766 while Present
(Comp
) loop
767 CC
:= Component_Clause
(Comp
);
769 -- If component clause is present, then deal with the non-default
770 -- bit order case for Ada 95 mode.
772 -- We only do this processing for the base type, and in fact that
773 -- is important, since otherwise if there are record subtypes, we
774 -- could reverse the bits once for each subtype, which is wrong.
776 if Present
(CC
) and then Ekind
(R
) = E_Record_Type
then
778 CFB
: constant Uint
:= Component_Bit_Offset
(Comp
);
779 CSZ
: constant Uint
:= Esize
(Comp
);
780 CLC
: constant Node_Id
:= Component_Clause
(Comp
);
781 Pos
: constant Node_Id
:= Position
(CLC
);
782 FB
: constant Node_Id
:= First_Bit
(CLC
);
784 Storage_Unit_Offset
: constant Uint
:=
785 CFB
/ System_Storage_Unit
;
787 Start_Bit
: constant Uint
:=
788 CFB
mod System_Storage_Unit
;
791 -- Cases where field goes over storage unit boundary
793 if Start_Bit
+ CSZ
> System_Storage_Unit
then
795 -- Allow multi-byte field but generate warning
797 if Start_Bit
mod System_Storage_Unit
= 0
798 and then CSZ
mod System_Storage_Unit
= 0
801 ("info: multi-byte field specified with non-standard "
802 & "Bit_Order?.v?", CLC
);
804 if Bytes_Big_Endian
then
806 ("\bytes are not reversed "
807 & "(component is big-endian)?.v?", CLC
);
810 ("\bytes are not reversed "
811 & "(component is little-endian)?.v?", CLC
);
814 -- Do not allow non-contiguous field
818 ("attempt to specify non-contiguous field not "
821 ("\caused by non-standard Bit_Order specified in "
822 & "legacy Ada 95 mode", CLC
);
825 -- Case where field fits in one storage unit
828 -- Give warning if suspicious component clause
830 if Intval
(FB
) >= System_Storage_Unit
831 and then Warn_On_Reverse_Bit_Order
834 ("info: Bit_Order clause does not affect byte "
835 & "ordering?.v?", Pos
);
837 Intval
(Pos
) + Intval
(FB
) /
840 ("info: position normalized to ^ before bit order "
841 & "interpreted?.v?", Pos
);
844 -- Here is where we fix up the Component_Bit_Offset value
845 -- to account for the reverse bit order. Some examples of
846 -- what needs to be done are:
848 -- First_Bit .. Last_Bit Component_Bit_Offset
860 -- The rule is that the first bit is obtained by subtracting
861 -- the old ending bit from storage_unit - 1.
863 Set_Component_Bit_Offset
(Comp
,
864 (Storage_Unit_Offset
* System_Storage_Unit
) +
865 (System_Storage_Unit
- 1) -
866 (Start_Bit
+ CSZ
- 1));
868 Set_Normalized_Position
(Comp
,
869 Component_Bit_Offset
(Comp
) / System_Storage_Unit
);
871 Set_Normalized_First_Bit
(Comp
,
872 Component_Bit_Offset
(Comp
) mod System_Storage_Unit
);
877 Next_Component_Or_Discriminant
(Comp
);
879 end Adjust_Record_For_Reverse_Bit_Order_Ada_95
;
881 -------------------------------------
882 -- Alignment_Check_For_Size_Change --
883 -------------------------------------
885 procedure Alignment_Check_For_Size_Change
(Typ
: Entity_Id
; Size
: Uint
) is
887 -- If the alignment is known, and not set by a rep clause, and is
888 -- inconsistent with the size being set, then reset it to unknown,
889 -- we assume in this case that the size overrides the inherited
890 -- alignment, and that the alignment must be recomputed.
892 if Known_Alignment
(Typ
)
893 and then not Has_Alignment_Clause
(Typ
)
894 and then Present
(Size
)
895 and then Size
mod (Alignment
(Typ
) * SSU
) /= 0
897 Reinit_Alignment
(Typ
);
899 end Alignment_Check_For_Size_Change
;
901 -----------------------------------
902 -- All_Membership_Choices_Static --
903 -----------------------------------
905 function All_Membership_Choices_Static
(Expr
: Node_Id
) return Boolean is
906 pragma Assert
(Nkind
(Expr
) in N_Membership_Test
);
909 (Present
(Right_Opnd
(Expr
))
911 Present
(Alternatives
(Expr
)));
913 if Present
(Right_Opnd
(Expr
)) then
914 return Is_Static_Choice
(Right_Opnd
(Expr
));
916 return All_Static_Choices
(Alternatives
(Expr
));
918 end All_Membership_Choices_Static
;
920 ------------------------
921 -- All_Static_Choices --
922 ------------------------
924 function All_Static_Choices
(L
: List_Id
) return Boolean is
929 while Present
(N
) loop
930 if not Is_Static_Choice
(N
) then
938 end All_Static_Choices
;
940 -------------------------------------
941 -- Analyze_Aspects_At_Freeze_Point --
942 -------------------------------------
944 procedure Analyze_Aspects_At_Freeze_Point
(E
: Entity_Id
) is
945 procedure Analyze_Aspect_Default_Value
(ASN
: Node_Id
);
946 -- This routine analyzes an Aspect_Default_[Component_]Value denoted by
947 -- the aspect specification node ASN.
949 procedure Check_Aspect_Too_Late
(N
: Node_Id
);
950 -- This procedure is similar to Rep_Item_Too_Late for representation
951 -- aspects that apply to type and that do not have a corresponding
953 -- Used to check in particular that the expression associated with
954 -- aspect node N for the given type (entity) of the aspect does not
955 -- appear too late according to the rules in RM 13.1(9) and 13.1(10).
957 procedure Make_Pragma_From_Boolean_Aspect
(ASN
: Node_Id
);
958 -- Given an aspect specification node ASN whose expression is an
959 -- optional Boolean, this routines creates the corresponding pragma
960 -- at the freezing point.
962 ----------------------------------
963 -- Analyze_Aspect_Default_Value --
964 ----------------------------------
966 procedure Analyze_Aspect_Default_Value
(ASN
: Node_Id
) is
967 Ent
: constant Entity_Id
:= Entity
(ASN
);
968 Expr
: constant Node_Id
:= Expression
(ASN
);
971 Set_Has_Default_Aspect
(Base_Type
(Ent
));
973 if Is_Scalar_Type
(Ent
) then
974 Set_Default_Aspect_Value
(Base_Type
(Ent
), Expr
);
976 Set_Default_Aspect_Component_Value
(Base_Type
(Ent
), Expr
);
979 Check_Aspect_Too_Late
(ASN
);
980 end Analyze_Aspect_Default_Value
;
982 ---------------------------
983 -- Check_Aspect_Too_Late --
984 ---------------------------
986 procedure Check_Aspect_Too_Late
(N
: Node_Id
) is
987 Typ
: constant Entity_Id
:= Entity
(N
);
988 Expr
: constant Node_Id
:= Expression
(N
);
990 function Find_Type_Reference
991 (Typ
: Entity_Id
; Expr
: Node_Id
) return Boolean;
992 -- Return True if a reference to type Typ is found in the expression
995 -------------------------
996 -- Find_Type_Reference --
997 -------------------------
999 function Find_Type_Reference
1000 (Typ
: Entity_Id
; Expr
: Node_Id
) return Boolean
1002 function Find_Type
(N
: Node_Id
) return Traverse_Result
;
1003 -- Set Found to True if N refers to Typ
1009 function Find_Type
(N
: Node_Id
) return Traverse_Result
is
1012 or else (Nkind
(N
) in N_Identifier | N_Expanded_Name
1013 and then Present
(Entity
(N
))
1014 and then Entity
(N
) = Typ
)
1022 function Search_Type_Reference
is new Traverse_Func
(Find_Type
);
1025 return Search_Type_Reference
(Expr
) = Abandon
;
1026 end Find_Type_Reference
;
1028 Parent_Type
: Entity_Id
;
1031 -- Ensure Expr is analyzed so that e.g. all types are properly
1032 -- resolved for Find_Type_Reference.
1036 -- A self-referential aspect is illegal if it forces freezing the
1037 -- entity before the corresponding aspect has been analyzed.
1039 if Find_Type_Reference
(Typ
, Expr
) then
1041 ("aspect specification causes premature freezing of&", N
, Typ
);
1044 -- For representation aspects, check for case of untagged derived
1045 -- type whose parent either has primitive operations (pre Ada 2022),
1046 -- or is a by-reference type (RM 13.1(10)).
1047 -- Strictly speaking the check also applies to Ada 2012 but it is
1048 -- really too constraining for existing code already, so relax it.
1049 -- ??? Confirming aspects should be allowed here.
1051 if Is_Representation_Aspect
(Get_Aspect_Id
(N
))
1052 and then Is_Derived_Type
(Typ
)
1053 and then not Is_Tagged_Type
(Typ
)
1055 Parent_Type
:= Etype
(Base_Type
(Typ
));
1057 if Ada_Version
<= Ada_2012
1058 and then Has_Primitive_Operations
(Parent_Type
)
1061 ("|representation aspect not permitted before Ada 2022: " &
1062 "use -gnat2022!", N
);
1064 ("\parent type & has primitive operations!", N
, Parent_Type
);
1066 elsif Is_By_Reference_Type
(Parent_Type
) then
1067 No_Type_Rep_Item
(N
);
1069 ("\parent type & is a by-reference type!", N
, Parent_Type
);
1072 end Check_Aspect_Too_Late
;
1074 -------------------------------------
1075 -- Make_Pragma_From_Boolean_Aspect --
1076 -------------------------------------
1078 procedure Make_Pragma_From_Boolean_Aspect
(ASN
: Node_Id
) is
1079 Ident
: constant Node_Id
:= Identifier
(ASN
);
1080 A_Name
: constant Name_Id
:= Chars
(Ident
);
1081 A_Id
: constant Aspect_Id
:= Get_Aspect_Id
(A_Name
);
1082 Ent
: constant Entity_Id
:= Entity
(ASN
);
1083 Expr
: constant Node_Id
:= Expression
(ASN
);
1084 Loc
: constant Source_Ptr
:= Sloc
(ASN
);
1086 procedure Check_False_Aspect_For_Derived_Type
;
1087 -- This procedure checks for the case of a false aspect for a derived
1088 -- type, which improperly tries to cancel an aspect inherited from
1091 -----------------------------------------
1092 -- Check_False_Aspect_For_Derived_Type --
1093 -----------------------------------------
1095 procedure Check_False_Aspect_For_Derived_Type
is
1099 -- We are only checking derived types
1101 if not Is_Derived_Type
(E
) then
1105 Par
:= Nearest_Ancestor
(E
);
1111 if not Is_Atomic
(Par
) then
1115 when Aspect_Atomic_Components
=>
1116 if not Has_Atomic_Components
(Par
) then
1120 when Aspect_Discard_Names
=>
1121 if not Discard_Names
(Par
) then
1126 if not Is_Packed
(Par
) then
1130 when Aspect_Unchecked_Union
=>
1131 if not Is_Unchecked_Union
(Par
) then
1135 when Aspect_Volatile
=>
1136 if not Is_Volatile
(Par
) then
1140 when Aspect_Volatile_Components
=>
1141 if not Has_Volatile_Components
(Par
) then
1145 when Aspect_Volatile_Full_Access
1146 | Aspect_Full_Access_Only
1148 if not Is_Volatile_Full_Access
(Par
) then
1156 -- Fall through means we are canceling an inherited aspect
1158 Error_Msg_Name_1
:= A_Name
;
1160 ("derived type& inherits aspect%, cannot cancel", Expr
, E
);
1161 end Check_False_Aspect_For_Derived_Type
;
1168 -- Start of processing for Make_Pragma_From_Boolean_Aspect
1171 if Present
(Expr
) and then Is_False
(Static_Boolean
(Expr
)) then
1172 Check_False_Aspect_For_Derived_Type
;
1175 -- There is no Full_Access_Only pragma so use VFA instead
1177 if A_Name
= Name_Full_Access_Only
then
1178 P_Name
:= Name_Volatile_Full_Access
;
1185 Pragma_Identifier
=>
1186 Make_Identifier
(Sloc
(Ident
), P_Name
),
1187 Pragma_Argument_Associations
=> New_List
(
1188 Make_Pragma_Argument_Association
(Sloc
(Ident
),
1189 Expression
=> New_Occurrence_Of
(Ent
, Sloc
(Ident
)))));
1191 Set_From_Aspect_Specification
(Prag
, True);
1192 Set_Corresponding_Aspect
(Prag
, ASN
);
1193 Set_Aspect_Rep_Item
(ASN
, Prag
);
1194 Set_Is_Delayed_Aspect
(Prag
);
1195 Set_Parent
(Prag
, ASN
);
1197 end Make_Pragma_From_Boolean_Aspect
;
1205 -- Start of processing for Analyze_Aspects_At_Freeze_Point
1208 -- Must be visible in current scope, but if this is a type from a nested
1209 -- package it may be frozen from an object declaration in the enclosing
1210 -- scope, so install the package declarations to complete the analysis
1211 -- of the aspects, if any. If the package itself is frozen the type will
1212 -- have been frozen as well.
1214 if not Scope_Within_Or_Same
(Current_Scope
, Scope
(E
)) then
1215 if Is_Type
(E
) and then From_Nested_Package
(E
) then
1217 Pack
: constant Entity_Id
:= Scope
(E
);
1221 Install_Visible_Declarations
(Pack
);
1222 Install_Private_Declarations
(Pack
);
1223 Analyze_Aspects_At_Freeze_Point
(E
);
1225 if Is_Private_Type
(E
)
1226 and then Present
(Full_View
(E
))
1228 Analyze_Aspects_At_Freeze_Point
(Full_View
(E
));
1231 End_Package_Scope
(Pack
);
1235 -- Aspects from other entities in different contexts are analyzed
1243 -- Look for aspect specification entries for this entity
1245 ASN
:= First_Rep_Item
(E
);
1246 while Present
(ASN
) loop
1247 if Nkind
(ASN
) = N_Aspect_Specification
then
1248 exit when Entity
(ASN
) /= E
;
1250 if Is_Delayed_Aspect
(ASN
) then
1251 A_Id
:= Get_Aspect_Id
(ASN
);
1255 -- For aspects whose expression is an optional Boolean, make
1256 -- the corresponding pragma at the freeze point.
1258 when Boolean_Aspects
1259 | Library_Unit_Aspects
1261 -- Aspects Export and Import require special handling.
1262 -- Both are by definition Boolean and may benefit from
1263 -- forward references, however their expressions are
1264 -- treated as static. In addition, the syntax of their
1265 -- corresponding pragmas requires extra "pieces" which
1266 -- may also contain forward references. To account for
1267 -- all of this, the corresponding pragma is created by
1268 -- Analyze_Aspect_Export_Import, but is not analyzed as
1269 -- the complete analysis must happen now.
1271 -- Aspect Full_Access_Only must be analyzed last so that
1272 -- aspects Volatile and Atomic, if any, are analyzed.
1274 -- Skip creation of pragma Preelaborable_Initialization
1275 -- in the case where the aspect has an expression,
1276 -- because the pragma is only needed for setting flag
1277 -- Known_To_Have_Preelab_Init, which is set by other
1278 -- means following resolution of the aspect expression.
1280 if A_Id
not in Aspect_Export
1281 | Aspect_Full_Access_Only
1283 and then (A_Id
/= Aspect_Preelaborable_Initialization
1284 or else No
(Expression
(ASN
)))
1286 Make_Pragma_From_Boolean_Aspect
(ASN
);
1289 -- Special handling for aspects that don't correspond to
1290 -- pragmas/attributes.
1292 when Aspect_Default_Value
1293 | Aspect_Default_Component_Value
1295 -- Do not inherit aspect for anonymous base type of a
1296 -- scalar or array type, because they apply to the first
1297 -- subtype of the type, and will be processed when that
1298 -- first subtype is frozen.
1300 if Is_Derived_Type
(E
)
1301 and then not Comes_From_Source
(E
)
1302 and then E
/= First_Subtype
(E
)
1306 Analyze_Aspect_Default_Value
(ASN
);
1309 -- Ditto for iterator aspects, because the corresponding
1310 -- attributes may not have been analyzed yet.
1312 when Aspect_Constant_Indexing
1313 | Aspect_Default_Iterator
1314 | Aspect_Iterator_Element
1315 | Aspect_Variable_Indexing
1317 Analyze
(Expression
(ASN
));
1319 if Etype
(Expression
(ASN
)) = Any_Type
then
1321 ("\aspect must be fully defined before & is frozen",
1325 when Aspect_Integer_Literal
1326 | Aspect_Real_Literal
1327 | Aspect_String_Literal
1329 Validate_Literal_Aspect
(E
, ASN
);
1331 when Aspect_Iterable
=>
1332 Validate_Iterable_Aspect
(E
, ASN
);
1334 when Aspect_Designated_Storage_Model
=>
1335 Analyze_And_Resolve
(Expression
(ASN
));
1337 if not Is_Entity_Name
(Expression
(ASN
))
1338 or else not Is_Object
(Entity
(Expression
(ASN
)))
1340 No
(Find_Aspect
(Etype
(Expression
(ASN
)),
1341 Aspect_Storage_Model_Type
))
1344 ("must specify name of stand-alone object of type "
1345 & "with aspect Storage_Model_Type",
1348 -- Set access type's Associated_Storage_Pool to denote
1349 -- the Storage_Model_Type object given for the aspect
1350 -- (even though that isn't actually an Ada storage pool).
1353 Set_Associated_Storage_Pool
1354 (E
, Entity
(Expression
(ASN
)));
1357 when Aspect_Storage_Model_Type
=>
1358 Validate_Storage_Model_Type_Aspect
(E
, ASN
);
1360 when Aspect_Aggregate
=>
1367 Ritem
:= Aspect_Rep_Item
(ASN
);
1369 if Present
(Ritem
) then
1375 Next_Rep_Item
(ASN
);
1378 -- Make a second pass for a Full_Access_Only entry
1380 ASN
:= First_Rep_Item
(E
);
1381 while Present
(ASN
) loop
1382 if Nkind
(ASN
) = N_Aspect_Specification
then
1383 exit when Entity
(ASN
) /= E
;
1385 if Get_Aspect_Id
(ASN
) = Aspect_Full_Access_Only
then
1386 Make_Pragma_From_Boolean_Aspect
(ASN
);
1387 Ritem
:= Aspect_Rep_Item
(ASN
);
1388 if Present
(Ritem
) then
1394 Next_Rep_Item
(ASN
);
1398 and then E
/= Base_Type
(E
)
1399 and then Is_First_Subtype
(E
)
1401 Inherit_Rep_Item_Chain
(Base_Type
(E
), E
);
1403 end Analyze_Aspects_At_Freeze_Point
;
1405 -----------------------------------
1406 -- Analyze_Aspect_Specifications --
1407 -----------------------------------
1409 procedure Analyze_Aspect_Specifications
(N
: Node_Id
; E
: Entity_Id
) is
1410 pragma Assert
(Present
(E
));
1412 procedure Decorate
(Asp
: Node_Id
; Prag
: Node_Id
);
1413 -- Establish linkages between an aspect and its corresponding pragma
1415 procedure Insert_Pragma
1417 Is_Instance
: Boolean := False);
1418 -- Subsidiary to the analysis of aspects
1420 -- Always_Terminates
1424 -- Constant_After_Elaboration
1427 -- Default_Initial_Condition
1428 -- Default_Storage_Pool
1432 -- Exceptional_Cases
1433 -- Extensions_Visible
1436 -- Initial_Condition
1438 -- Max_Entry_Queue_Depth
1439 -- Max_Entry_Queue_Length
1451 -- Secondary_Stack_Size
1452 -- Subprogram_Variant
1453 -- Volatile_Function
1455 -- Insert pragma Prag such that it mimics the placement of a source
1456 -- pragma of the same kind. Flag Is_Generic should be set when the
1457 -- context denotes a generic instance.
1459 function Relocate_Expression
(Source
: Node_Id
) return Node_Id
;
1460 -- Outside of a generic this function is equivalent to Relocate_Node.
1461 -- Inside a generic it is an identity function, because Relocate_Node
1462 -- would create a new node that is not associated with the generic
1463 -- template. This association is needed to save references to entities
1464 -- that are global to the generic (and might be not visible from where
1465 -- the generic is instantiated).
1467 -- Inside a generic the original tree is shared between aspect and
1468 -- a corresponding pragma (or an attribute definition clause). This
1469 -- parallels what is done in sem_prag.adb (see Get_Argument).
1475 procedure Decorate
(Asp
: Node_Id
; Prag
: Node_Id
) is
1477 Set_Aspect_Rep_Item
(Asp
, Prag
);
1478 Set_Corresponding_Aspect
(Prag
, Asp
);
1479 Set_From_Aspect_Specification
(Prag
);
1480 Set_Parent
(Prag
, Asp
);
1487 procedure Insert_Pragma
1489 Is_Instance
: Boolean := False)
1495 Inserted
: Boolean := False;
1498 -- When the aspect appears on an entry, package, protected unit,
1499 -- subprogram, or task unit body, insert the generated pragma at the
1500 -- top of the body declarations to emulate the behavior of a source
1503 -- package body Pack with Aspect is
1505 -- package body Pack is
1508 if Nkind
(N
) in N_Entry_Body
1514 Decls
:= Declarations
(N
);
1518 Set_Declarations
(N
, Decls
);
1521 Prepend_To
(Decls
, Prag
);
1523 -- When the aspect is associated with a [generic] package declaration
1524 -- insert the generated pragma at the top of the visible declarations
1525 -- to emulate the behavior of a source pragma.
1527 -- package Pack with Aspect is
1532 elsif Nkind
(N
) in N_Generic_Package_Declaration
1533 | N_Package_Declaration
1535 Decls
:= Visible_Declarations
(Specification
(N
));
1539 Set_Visible_Declarations
(Specification
(N
), Decls
);
1542 -- The visible declarations of a generic instance have the
1543 -- following structure:
1545 -- <renamings of generic formals>
1546 -- <renamings of internally-generated spec and body>
1547 -- <first source declaration>
1549 -- Insert the pragma before the first source declaration by
1550 -- skipping the instance "header" to ensure proper visibility of
1554 Decl
:= First
(Decls
);
1555 while Present
(Decl
) loop
1556 if Comes_From_Source
(Decl
) then
1557 Insert_Before
(Decl
, Prag
);
1565 -- The pragma is placed after the instance "header"
1567 if not Inserted
then
1568 Append_To
(Decls
, Prag
);
1571 -- Otherwise this is not a generic instance
1574 Prepend_To
(Decls
, Prag
);
1577 -- When the aspect is associated with a protected unit declaration,
1578 -- insert the generated pragma at the top of the visible declarations
1579 -- the emulate the behavior of a source pragma.
1581 -- protected [type] Prot with Aspect is
1583 -- protected [type] Prot is
1586 elsif Nkind
(N
) = N_Protected_Type_Declaration
then
1587 Def
:= Protected_Definition
(N
);
1591 Make_Protected_Definition
(Sloc
(N
),
1592 Visible_Declarations
=> New_List
,
1593 End_Label
=> Empty
);
1595 Set_Protected_Definition
(N
, Def
);
1598 Decls
:= Visible_Declarations
(Def
);
1602 Set_Visible_Declarations
(Def
, Decls
);
1605 Prepend_To
(Decls
, Prag
);
1607 -- When the aspect is associated with a task unit declaration, insert
1608 -- insert the generated pragma at the top of the visible declarations
1609 -- the emulate the behavior of a source pragma.
1611 -- task [type] Prot with Aspect is
1613 -- task [type] Prot is
1616 elsif Nkind
(N
) = N_Task_Type_Declaration
then
1617 Def
:= Task_Definition
(N
);
1621 Make_Task_Definition
(Sloc
(N
),
1622 Visible_Declarations
=> New_List
,
1623 End_Label
=> Empty
);
1625 Set_Task_Definition
(N
, Def
);
1628 Decls
:= Visible_Declarations
(Def
);
1632 Set_Visible_Declarations
(Def
, Decls
);
1635 Prepend_To
(Decls
, Prag
);
1637 -- When the context is a library unit, the pragma is added to the
1638 -- Pragmas_After list.
1640 elsif Nkind
(Parent
(N
)) = N_Compilation_Unit
then
1641 Aux
:= Aux_Decls_Node
(Parent
(N
));
1643 if No
(Pragmas_After
(Aux
)) then
1644 Set_Pragmas_After
(Aux
, New_List
);
1647 Prepend
(Prag
, Pragmas_After
(Aux
));
1649 -- Default, the pragma is inserted after the context
1652 Insert_After
(N
, Prag
);
1656 -------------------------
1657 -- Relocate_Expression --
1658 -------------------------
1660 function Relocate_Expression
(Source
: Node_Id
) return Node_Id
is
1662 if Inside_A_Generic
then
1665 return Atree
.Relocate_Node
(Source
);
1667 end Relocate_Expression
;
1672 Aitem
: Node_Id
:= Empty
;
1675 L
: constant List_Id
:= Aspect_Specifications
(N
);
1677 Ins_Node
: Node_Id
:= N
;
1678 -- Insert pragmas/attribute definition clause after this node when no
1679 -- delayed analysis is required.
1681 -- Start of processing for Analyze_Aspect_Specifications
1684 -- The general processing involves building an attribute definition
1685 -- clause or a pragma node that corresponds to the aspect. Then in order
1686 -- to delay the evaluation of this aspect to the freeze point, we attach
1687 -- the corresponding pragma/attribute definition clause to the aspect
1688 -- specification node, which is then placed in the Rep Item chain. In
1689 -- this case we mark the entity by setting the flag Has_Delayed_Aspects
1690 -- and we evaluate the rep item at the freeze point. When the aspect
1691 -- doesn't have a corresponding pragma/attribute definition clause, then
1692 -- its analysis is simply delayed at the freeze point.
1694 -- Some special cases don't require delay analysis, thus the aspect is
1695 -- analyzed right now.
1697 -- Note that there is a special handling for Pre, Post, Test_Case,
1698 -- Contract_Cases, Always_Terminates, Exceptional_Cases and
1699 -- Subprogram_Variant aspects. In these cases, we do not have to worry
1700 -- about delay issues, since the pragmas themselves deal with delay of
1701 -- visibility for the expression analysis. Thus, we just insert the
1702 -- pragma after the node N.
1708 -- Loop through aspects
1710 Aspect
:= First
(L
);
1711 Aspect_Loop
: while Present
(Aspect
) loop
1712 Analyze_One_Aspect
: declare
1714 Aspect_Exit
: exception;
1715 -- This exception is used to exit aspect processing completely. It
1716 -- is used when an error is detected, and no further processing is
1717 -- required. It is also used if an earlier error has left the tree
1718 -- in a state where the aspect should not be processed.
1720 Expr
: constant Node_Id
:= Expression
(Aspect
);
1721 Id
: constant Node_Id
:= Identifier
(Aspect
);
1722 Loc
: constant Source_Ptr
:= Sloc
(Aspect
);
1723 Nam
: constant Name_Id
:= Chars
(Id
);
1724 A_Id
: constant Aspect_Id
:= Get_Aspect_Id
(Nam
);
1727 Delay_Required
: Boolean;
1728 -- Set False if delay is not required
1730 Eloc
: Source_Ptr
:= No_Location
;
1731 -- Source location of expression, modified when we split PPC's. It
1732 -- is set below when Expr is present.
1734 procedure Analyze_Aspect_Convention
;
1735 -- Perform analysis of aspect Convention
1737 procedure Analyze_Aspect_Disable_Controlled
;
1738 -- Perform analysis of aspect Disable_Controlled
1740 procedure Analyze_Aspect_Export_Import
;
1741 -- Perform analysis of aspects Export or Import
1743 procedure Analyze_Aspect_External_Link_Name
;
1744 -- Perform analysis of aspects External_Name or Link_Name
1746 procedure Analyze_Aspect_Implicit_Dereference
;
1747 -- Perform analysis of the Implicit_Dereference aspects
1749 procedure Analyze_Aspect_Relaxed_Initialization
;
1750 -- Perform analysis of aspect Relaxed_Initialization
1752 procedure Analyze_Aspect_Yield
;
1753 -- Perform analysis of aspect Yield
1755 procedure Analyze_Aspect_Static
;
1756 -- Ada 2022 (AI12-0075): Perform analysis of aspect Static
1758 procedure Check_Expr_Is_OK_Static_Expression
1760 Typ
: Entity_Id
:= Empty
);
1761 -- Check the specified expression Expr to make sure that it is a
1762 -- static expression of the given type (i.e. it will be analyzed
1763 -- and resolved using this type, which can be any valid argument
1764 -- to Resolve, e.g. Any_Integer is OK). If not, give an error
1765 -- and raise Aspect_Exit. If Typ is left Empty, then any static
1766 -- expression is allowed. Includes checking that the expression
1767 -- does not raise Constraint_Error.
1769 function Directly_Specified
1770 (Id
: Entity_Id
; A
: Aspect_Id
) return Boolean;
1771 -- Returns True if the given aspect is directly (as opposed to
1772 -- via any form of inheritance) specified for the given entity.
1774 function Make_Aitem_Pragma
1775 (Pragma_Argument_Associations
: List_Id
;
1776 Pragma_Name
: Name_Id
) return Node_Id
;
1777 -- This is a wrapper for Make_Pragma used for converting aspects
1778 -- to pragmas. It takes care of Sloc (set from Loc) and building
1779 -- the pragma identifier from the given name. In addition the
1780 -- flags Class_Present and Split_PPC are set from the aspect
1781 -- node, as well as Is_Ignored. This routine also sets the
1782 -- From_Aspect_Specification in the resulting pragma node to
1783 -- True, and sets Corresponding_Aspect to point to the aspect.
1784 -- The resulting pragma is assigned to Aitem.
1786 -------------------------------
1787 -- Analyze_Aspect_Convention --
1788 -------------------------------
1790 procedure Analyze_Aspect_Convention
is
1799 -- Obtain all interfacing aspects that apply to the related
1802 Get_Interfacing_Aspects
1803 (Iface_Asp
=> Aspect
,
1804 Conv_Asp
=> Dummy_1
,
1811 -- The related entity is subject to aspect Export or Import.
1812 -- Do not process Convention now because it must be analysed
1813 -- as part of Export or Import.
1815 if Present
(Expo
) or else Present
(Imp
) then
1818 -- Otherwise Convention appears by itself
1821 -- The aspect specifies a particular convention
1823 if Present
(Expr
) then
1824 Conv
:= New_Copy_Tree
(Expr
);
1826 -- Otherwise assume convention Ada
1829 Conv
:= Make_Identifier
(Loc
, Name_Ada
);
1833 -- pragma Convention (<Conv>, <E>);
1835 Aitem
:= Make_Aitem_Pragma
1836 (Pragma_Name
=> Name_Convention
,
1837 Pragma_Argument_Associations
=> New_List
(
1838 Make_Pragma_Argument_Association
(Loc
,
1839 Expression
=> Conv
),
1840 Make_Pragma_Argument_Association
(Loc
,
1841 Expression
=> New_Occurrence_Of
(E
, Loc
))));
1843 Decorate
(Aspect
, Aitem
);
1844 Insert_Pragma
(Aitem
);
1846 end Analyze_Aspect_Convention
;
1848 ---------------------------------------
1849 -- Analyze_Aspect_Disable_Controlled --
1850 ---------------------------------------
1852 procedure Analyze_Aspect_Disable_Controlled
is
1854 -- The aspect applies only to controlled records
1856 if not (Ekind
(E
) = E_Record_Type
1857 and then Is_Controlled_Active
(E
))
1860 ("aspect % requires controlled record type", Aspect
);
1864 -- Preanalyze the expression (if any) when the aspect resides
1865 -- in a generic unit.
1867 if Inside_A_Generic
then
1868 if Present
(Expr
) then
1869 Preanalyze_And_Resolve
(Expr
, Any_Boolean
);
1872 -- Otherwise the aspect resides in a nongeneric context
1875 -- A controlled record type loses its controlled semantics
1876 -- when the expression statically evaluates to True.
1878 if Present
(Expr
) then
1879 Analyze_And_Resolve
(Expr
, Any_Boolean
);
1881 if Is_OK_Static_Expression
(Expr
) then
1882 if Is_True
(Static_Boolean
(Expr
)) then
1883 Set_Disable_Controlled
(E
);
1886 -- Otherwise the expression is not static
1890 ("expression of aspect % must be static", Aspect
);
1893 -- Otherwise the aspect appears without an expression and
1894 -- defaults to True.
1897 Set_Disable_Controlled
(E
);
1900 end Analyze_Aspect_Disable_Controlled
;
1902 ----------------------------------
1903 -- Analyze_Aspect_Export_Import --
1904 ----------------------------------
1906 procedure Analyze_Aspect_Export_Import
is
1914 -- Obtain all interfacing aspects that apply to the related
1917 Get_Interfacing_Aspects
1918 (Iface_Asp
=> Aspect
,
1919 Conv_Asp
=> Dummy_1
,
1926 -- The related entity cannot be subject to both aspects Export
1929 if Present
(Expo
) and then Present
(Imp
) then
1931 ("incompatible interfacing aspects given for &", E
);
1932 Error_Msg_Sloc
:= Sloc
(Expo
);
1933 Error_Msg_N
("\aspect Export #", E
);
1934 Error_Msg_Sloc
:= Sloc
(Imp
);
1935 Error_Msg_N
("\aspect Import #", E
);
1938 -- A variable is most likely modified from the outside. Take
1939 -- the optimistic approach to avoid spurious errors.
1941 if Ekind
(E
) = E_Variable
then
1942 Set_Never_Set_In_Source
(E
, False);
1945 -- Resolve the expression of an Import or Export here, and
1946 -- require it to be of type Boolean and static. This is not
1947 -- quite right, because in general this should be delayed,
1948 -- but that seems tricky for these, because normally Boolean
1949 -- aspects are replaced with pragmas at the freeze point in
1950 -- Make_Pragma_From_Boolean_Aspect.
1953 or else Is_True
(Static_Boolean
(Expr
))
1955 if A_Id
= Aspect_Import
then
1956 Set_Has_Completion
(E
);
1957 Set_Is_Imported
(E
);
1959 -- An imported object cannot be explicitly initialized
1961 if Nkind
(N
) = N_Object_Declaration
1962 and then Present
(Expression
(N
))
1965 ("imported entities cannot be initialized "
1966 & "(RM B.1(24))", Expression
(N
));
1970 pragma Assert
(A_Id
= Aspect_Export
);
1971 Set_Is_Exported
(E
);
1974 -- Create the proper form of pragma Export or Import taking
1975 -- into account Conversion, External_Name, and Link_Name.
1977 Aitem
:= Build_Export_Import_Pragma
(Aspect
, E
);
1979 -- Otherwise the expression is either False or erroneous. There
1980 -- is no corresponding pragma.
1985 end Analyze_Aspect_Export_Import
;
1987 ---------------------------------------
1988 -- Analyze_Aspect_External_Link_Name --
1989 ---------------------------------------
1991 procedure Analyze_Aspect_External_Link_Name
is
1999 -- Obtain all interfacing aspects that apply to the related
2002 Get_Interfacing_Aspects
2003 (Iface_Asp
=> Aspect
,
2004 Conv_Asp
=> Dummy_1
,
2011 -- Ensure that aspect External_Name applies to aspect Export or
2014 if A_Id
= Aspect_External_Name
then
2015 if No
(Expo
) and then No
(Imp
) then
2017 ("aspect External_Name requires aspect Import or "
2018 & "Export", Aspect
);
2021 -- Otherwise ensure that aspect Link_Name applies to aspect
2022 -- Export or Import.
2025 pragma Assert
(A_Id
= Aspect_Link_Name
);
2026 if No
(Expo
) and then No
(Imp
) then
2028 ("aspect Link_Name requires aspect Import or Export",
2032 end Analyze_Aspect_External_Link_Name
;
2034 -----------------------------------------
2035 -- Analyze_Aspect_Implicit_Dereference --
2036 -----------------------------------------
2038 procedure Analyze_Aspect_Implicit_Dereference
is
2040 if not Is_Type
(E
) or else not Has_Discriminants
(E
) then
2042 ("aspect must apply to a type with discriminants", Expr
);
2044 elsif not Is_Entity_Name
(Expr
) then
2046 ("aspect must name a discriminant of current type", Expr
);
2049 -- Discriminant type be an anonymous access type or an
2050 -- anonymous access to subprogram.
2052 -- Missing synchronized types???
2055 Disc
: Entity_Id
:= First_Discriminant
(E
);
2057 while Present
(Disc
) loop
2058 if Chars
(Expr
) = Chars
(Disc
)
2059 and then Ekind
(Etype
(Disc
)) in
2060 E_Anonymous_Access_Subprogram_Type |
2061 E_Anonymous_Access_Type
2063 Set_Has_Implicit_Dereference
(E
);
2064 Set_Has_Implicit_Dereference
(Disc
);
2068 Next_Discriminant
(Disc
);
2071 -- Error if no proper access discriminant
2073 if Present
(Disc
) then
2074 -- For a type extension, check whether parent has
2075 -- a reference discriminant, to verify that use is
2078 if Is_Derived_Type
(E
)
2079 and then Has_Discriminants
(Etype
(E
))
2082 Parent_Disc
: constant Entity_Id
:=
2083 Get_Reference_Discriminant
(Etype
(E
));
2085 if Present
(Parent_Disc
)
2086 and then Corresponding_Discriminant
(Disc
) /=
2090 ("reference discriminant does not match "
2091 & "discriminant of parent type", Expr
);
2098 ("not an access discriminant of&", Expr
, E
);
2103 end Analyze_Aspect_Implicit_Dereference
;
2105 -------------------------------------------
2106 -- Analyze_Aspect_Relaxed_Initialization --
2107 -------------------------------------------
2109 procedure Analyze_Aspect_Relaxed_Initialization
is
2110 procedure Analyze_Relaxed_Parameter
2111 (Subp_Id
: Entity_Id
;
2113 Seen
: in out Elist_Id
);
2114 -- Analyze parameter that appears in the expression of the
2115 -- aspect Relaxed_Initialization.
2117 -------------------------------
2118 -- Analyze_Relaxed_Parameter --
2119 -------------------------------
2121 procedure Analyze_Relaxed_Parameter
2122 (Subp_Id
: Entity_Id
;
2124 Seen
: in out Elist_Id
)
2127 -- Set name of the aspect for error messages
2128 Error_Msg_Name_1
:= Nam
;
2130 -- The relaxed parameter is a formal parameter
2132 if Nkind
(Param
) in N_Identifier | N_Expanded_Name
then
2136 Item
: constant Entity_Id
:= Entity
(Param
);
2138 -- It must be a formal of the analyzed subprogram
2140 if Scope
(Item
) = Subp_Id
then
2142 pragma Assert
(Is_Formal
(Item
));
2144 -- It must not have scalar or access type
2146 if Is_Elementary_Type
(Etype
(Item
)) then
2147 Error_Msg_N
("illegal aspect % item", Param
);
2149 ("\item must not have elementary type", Param
);
2152 -- Detect duplicated items
2154 if Contains
(Seen
, Item
) then
2155 Error_Msg_N
("duplicate aspect % item", Param
);
2157 Append_New_Elmt
(Item
, Seen
);
2160 Error_Msg_N
("illegal aspect % item", Param
);
2164 -- The relaxed parameter is the function's Result attribute
2166 elsif Is_Attribute_Result
(Param
) then
2170 Pref
: constant Node_Id
:= Prefix
(Param
);
2174 Nkind
(Pref
) in N_Identifier | N_Expanded_Name
2176 Entity
(Pref
) = Subp_Id
2178 -- Function result must not have scalar or access
2181 if Is_Elementary_Type
(Etype
(Pref
)) then
2182 Error_Msg_N
("illegal aspect % item", Param
);
2184 ("\function result must not have elementary"
2188 -- Detect duplicated items
2190 if Contains
(Seen
, Subp_Id
) then
2191 Error_Msg_N
("duplicate aspect % item", Param
);
2193 Append_New_Elmt
(Entity
(Pref
), Seen
);
2197 Error_Msg_N
("illegal aspect % item", Param
);
2201 Error_Msg_N
("illegal aspect % item", Param
);
2203 end Analyze_Relaxed_Parameter
;
2207 Seen
: Elist_Id
:= No_Elist
;
2208 -- Items that appear in the relaxed initialization aspect
2209 -- expression of a subprogram; for detecting duplicates.
2211 Restore_Scope
: Boolean;
2212 -- Will be set to True if we need to restore the scope table
2213 -- after analyzing the aspect expression.
2215 Prev_Id
: Entity_Id
;
2217 -- Start of processing for Analyze_Aspect_Relaxed_Initialization
2220 -- Set name of the aspect for error messages
2221 Error_Msg_Name_1
:= Nam
;
2223 -- Annotation of a type; no aspect expression is allowed.
2224 -- For a private type, the aspect must be attached to the
2227 -- ??? Once the exact rule for this aspect is ready, we will
2228 -- likely reject concurrent types, etc., so let's keep the code
2229 -- for types and variable separate.
2231 if Is_First_Subtype
(E
) then
2232 Prev_Id
:= Incomplete_Or_Partial_View
(E
);
2233 if Present
(Prev_Id
) then
2235 -- Aspect may appear on the full view of an incomplete
2236 -- type because the incomplete declaration cannot have
2239 if Ekind
(Prev_Id
) = E_Incomplete_Type
then
2242 Error_Msg_N
("aspect % must apply to partial view", N
);
2245 elsif Present
(Expr
) then
2246 Error_Msg_N
("illegal aspect % expression", Expr
);
2249 -- Annotation of a variable; no aspect expression is allowed
2251 elsif Ekind
(E
) = E_Variable
then
2252 if Present
(Expr
) then
2253 Error_Msg_N
("illegal aspect % expression", Expr
);
2256 -- Annotation of a constant; no aspect expression is allowed.
2257 -- For a deferred constant, the aspect must be attached to the
2260 elsif Ekind
(E
) = E_Constant
then
2261 if Present
(Incomplete_Or_Partial_View
(E
)) then
2263 ("aspect % must apply to deferred constant", N
);
2265 elsif Present
(Expr
) then
2266 Error_Msg_N
("illegal aspect % expression", Expr
);
2269 -- Annotation of a subprogram; aspect expression is required
2271 elsif Is_Subprogram_Or_Entry
(E
)
2272 or else Is_Generic_Subprogram
(E
)
2274 if Present
(Expr
) then
2276 -- If we analyze subprogram body that acts as its own
2277 -- spec, then the subprogram itself and its formals are
2278 -- already installed; otherwise, we need to install them,
2279 -- as they must be visible when analyzing the aspect
2282 if In_Open_Scopes
(E
) then
2283 Restore_Scope
:= False;
2285 Restore_Scope
:= True;
2288 -- Only formals of the subprogram itself can appear
2289 -- in Relaxed_Initialization aspect expression, not
2290 -- formals of the enclosing generic unit. (This is
2291 -- different than in Precondition or Depends aspects,
2292 -- where both kinds of formals are allowed.)
2294 Install_Formals
(E
);
2297 -- Aspect expression is either an aggregate with list of
2298 -- parameters (and possibly the Result attribute for a
2301 if Nkind
(Expr
) = N_Aggregate
then
2303 -- Component associations in the aggregate must be a
2304 -- parameter name followed by a static boolean
2307 if Present
(Component_Associations
(Expr
)) then
2310 First
(Component_Associations
(Expr
));
2312 while Present
(Assoc
) loop
2313 if List_Length
(Choices
(Assoc
)) = 1 then
2314 Analyze_Relaxed_Parameter
2315 (E
, First
(Choices
(Assoc
)), Seen
);
2317 if Inside_A_Generic
then
2318 Preanalyze_And_Resolve
2319 (Expression
(Assoc
), Any_Boolean
);
2322 (Expression
(Assoc
), Any_Boolean
);
2325 if not Is_OK_Static_Expression
2326 (Expression
(Assoc
))
2328 Error_Msg_Name_1
:= Nam
;
2330 ("expression of aspect % " &
2331 "must be static", Aspect
);
2335 Error_Msg_Name_1
:= Nam
;
2337 ("illegal aspect % expression", Expr
);
2344 -- Expressions of the aggregate are parameter names
2346 if Present
(Expressions
(Expr
)) then
2348 Param
: Node_Id
:= First
(Expressions
(Expr
));
2351 while Present
(Param
) loop
2352 Analyze_Relaxed_Parameter
(E
, Param
, Seen
);
2358 -- Mark the aggregate expression itself as analyzed;
2359 -- its subexpressions were marked when they themselves
2362 Set_Analyzed
(Expr
);
2364 -- Otherwise, it is a single name of a subprogram
2365 -- parameter (or possibly the Result attribute for
2369 Analyze_Relaxed_Parameter
(E
, Expr
, Seen
);
2372 if Restore_Scope
then
2376 Error_Msg_N
("missing expression for aspect %", N
);
2380 Error_Msg_N
("inappropriate entity for aspect %", E
);
2382 end Analyze_Aspect_Relaxed_Initialization
;
2384 ---------------------------
2385 -- Analyze_Aspect_Static --
2386 ---------------------------
2388 procedure Analyze_Aspect_Static
is
2389 function Has_Convention_Intrinsic
(L
: List_Id
) return Boolean;
2390 -- Return True if L contains a pragma argument association
2391 -- node representing a convention Intrinsic.
2393 ------------------------------
2394 -- Has_Convention_Intrinsic --
2395 ------------------------------
2397 function Has_Convention_Intrinsic
2398 (L
: List_Id
) return Boolean
2400 Arg
: Node_Id
:= First
(L
);
2402 while Present
(Arg
) loop
2403 if Nkind
(Arg
) = N_Pragma_Argument_Association
2404 and then Chars
(Arg
) = Name_Convention
2405 and then Chars
(Expression
(Arg
)) = Name_Intrinsic
2414 end Has_Convention_Intrinsic
;
2416 Is_Imported_Intrinsic
: Boolean;
2419 if Ada_Version
< Ada_2022
then
2420 Error_Msg_Ada_2022_Feature
("aspect %", Sloc
(Aspect
));
2424 Is_Imported_Intrinsic
:= Is_Imported
(E
)
2426 Has_Convention_Intrinsic
2427 (Pragma_Argument_Associations
(Import_Pragma
(E
)));
2429 -- The aspect applies only to expression functions that
2430 -- statisfy the requirements for a static expression function
2431 -- (such as having an expression that is predicate-static) as
2432 -- well as Intrinsic imported functions as a -gnatX extension.
2434 if not Is_Expression_Function
(E
)
2436 not (All_Extensions_Allowed
and then Is_Imported_Intrinsic
)
2438 if All_Extensions_Allowed
then
2440 ("aspect % requires intrinsic or expression function",
2443 elsif Is_Imported_Intrinsic
then
2444 Error_Msg_GNAT_Extension
2445 ("aspect % on intrinsic function", Sloc
(Aspect
),
2446 Is_Core_Extension
=> True);
2450 ("aspect % requires expression function", Aspect
);
2455 -- Ada 2022 (AI12-0075): Check that the function satisfies
2456 -- several requirements of static functions as specified in
2457 -- RM 6.8(5.1-5.8). Note that some of the requirements given
2458 -- there are checked elsewhere.
2461 -- The expression of the expression function must be a
2462 -- potentially static expression (RM 2022 6.8(3.2-3.4)).
2463 -- That's checked in Sem_Ch6.Analyze_Expression_Function.
2465 -- The function must not contain any calls to itself, which
2466 -- is checked in Sem_Res.Resolve_Call.
2468 -- Each formal must be of mode in and have a static subtype
2471 Formal
: Entity_Id
:= First_Formal
(E
);
2473 while Present
(Formal
) loop
2474 if Ekind
(Formal
) /= E_In_Parameter
then
2476 ("aspect % requires formals of mode IN",
2482 if not Is_Static_Subtype
(Etype
(Formal
)) then
2484 ("aspect % requires formals with static subtypes",
2490 Next_Formal
(Formal
);
2494 -- The function's result subtype must be a static subtype
2496 if not Is_Static_Subtype
(Etype
(E
)) then
2498 ("aspect % requires function with result of "
2499 & "a static subtype",
2505 -- Check that the function does not have any applicable
2506 -- precondition or postcondition expression.
2508 for Asp
in Pre_Post_Aspects
loop
2509 if Has_Aspect
(E
, Asp
) then
2510 Error_Msg_Name_1
:= Aspect_Names
(Asp
);
2512 ("aspect % is not allowed for a static "
2513 & "expression function",
2514 Find_Aspect
(E
, Asp
));
2520 -- ??? Must check that "for result type R, if the
2521 -- function is a boundary entity for type R (see 7.3.2),
2522 -- no type invariant applies to type R; if R has a
2523 -- component type C, a similar rule applies to C."
2526 -- When the expression is present, it must be static. If it
2527 -- evaluates to True, the expression function is treated as
2528 -- a static function. Otherwise the aspect appears without
2529 -- an expression and defaults to True.
2531 if Present
(Expr
) then
2532 -- Preanalyze the expression when the aspect resides in a
2533 -- generic unit. (Is this generic-related code necessary
2534 -- for this aspect? It's modeled on what's done for aspect
2535 -- Disable_Controlled. ???)
2537 if Inside_A_Generic
then
2538 Preanalyze_And_Resolve
(Expr
, Any_Boolean
);
2540 -- Otherwise the aspect resides in a nongeneric context
2543 Analyze_And_Resolve
(Expr
, Any_Boolean
);
2545 -- Error if the boolean expression is not static
2547 if not Is_OK_Static_Expression
(Expr
) then
2549 ("expression of aspect % must be static", Aspect
);
2553 end Analyze_Aspect_Static
;
2555 --------------------------
2556 -- Analyze_Aspect_Yield --
2557 --------------------------
2559 procedure Analyze_Aspect_Yield
is
2560 Expr_Value
: Boolean := False;
2563 -- Check valid entity for 'Yield
2565 if (Is_Subprogram
(E
)
2566 or else Is_Generic_Subprogram
(E
)
2567 or else Is_Entry
(E
))
2568 and then not Within_Protected_Type
(E
)
2572 elsif Within_Protected_Type
(E
) then
2574 ("aspect% not applicable to protected operation", Id
);
2579 ("aspect% only applicable to subprogram and entry "
2580 & "declarations", Id
);
2584 -- Evaluate its static expression (if available); otherwise it
2585 -- defaults to True.
2590 -- Otherwise it must have a static boolean expression
2593 if Inside_A_Generic
then
2594 Preanalyze_And_Resolve
(Expr
, Any_Boolean
);
2596 Analyze_And_Resolve
(Expr
, Any_Boolean
);
2599 if Is_OK_Static_Expression
(Expr
) then
2600 if Is_True
(Static_Boolean
(Expr
)) then
2605 ("expression of aspect % must be static", Aspect
);
2610 Set_Has_Yield_Aspect
(E
);
2613 -- If the Yield aspect is specified for a dispatching
2614 -- subprogram that inherits the aspect, the specified
2615 -- value shall be confirming.
2618 and then Is_Dispatching_Operation
(E
)
2619 and then Present
(Overridden_Operation
(E
))
2620 and then Has_Yield_Aspect
(Overridden_Operation
(E
))
2621 /= Is_True
(Static_Boolean
(Expr
))
2623 Error_Msg_N
("specification of inherited aspect% can only " &
2624 "confirm parent value", Id
);
2626 end Analyze_Aspect_Yield
;
2628 ----------------------------------------
2629 -- Check_Expr_Is_OK_Static_Expression --
2630 ----------------------------------------
2632 procedure Check_Expr_Is_OK_Static_Expression
2634 Typ
: Entity_Id
:= Empty
)
2637 if Present
(Typ
) then
2638 Analyze_And_Resolve
(Expr
, Typ
);
2640 Analyze_And_Resolve
(Expr
);
2643 -- An expression cannot be considered static if its resolution
2644 -- failed or if it's erroneous. Stop the analysis of the
2647 if Etype
(Expr
) = Any_Type
or else Error_Posted
(Expr
) then
2650 elsif Is_OK_Static_Expression
(Expr
) then
2653 -- Finally, we have a real error
2656 Error_Msg_Name_1
:= Nam
;
2657 Flag_Non_Static_Expr
2658 ("entity for aspect% must be a static expression",
2662 end Check_Expr_Is_OK_Static_Expression
;
2664 ------------------------
2665 -- Directly_Specified --
2666 ------------------------
2668 function Directly_Specified
2669 (Id
: Entity_Id
; A
: Aspect_Id
) return Boolean
2671 Aspect_Spec
: constant Node_Id
:= Find_Aspect
(Id
, A
);
2673 return Present
(Aspect_Spec
) and then Entity
(Aspect_Spec
) = Id
;
2674 end Directly_Specified
;
2676 -----------------------
2677 -- Make_Aitem_Pragma --
2678 -----------------------
2680 function Make_Aitem_Pragma
2681 (Pragma_Argument_Associations
: List_Id
;
2682 Pragma_Name
: Name_Id
) return Node_Id
2684 Args
: List_Id
:= Pragma_Argument_Associations
;
2688 -- We should never get here if aspect was disabled
2690 pragma Assert
(not Is_Disabled
(Aspect
));
2692 -- Certain aspects allow for an optional name or expression. Do
2693 -- not generate a pragma with empty argument association list.
2695 if No
(Args
) or else No
(Expression
(First
(Args
))) then
2703 Pragma_Argument_Associations
=> Args
,
2704 Pragma_Identifier
=>
2705 Make_Identifier
(Sloc
(Id
), Pragma_Name
),
2706 Class_Present
=> Class_Present
(Aspect
),
2707 Split_PPC
=> Split_PPC
(Aspect
));
2709 -- Set additional semantic fields
2711 if Is_Ignored
(Aspect
) then
2712 Set_Is_Ignored
(Aitem
);
2713 elsif Is_Checked
(Aspect
) then
2714 Set_Is_Checked
(Aitem
);
2717 Set_Corresponding_Aspect
(Aitem
, Aspect
);
2718 Set_From_Aspect_Specification
(Aitem
);
2721 end Make_Aitem_Pragma
;
2723 -- Start of processing for Analyze_One_Aspect
2726 -- Skip aspect if already analyzed, to avoid looping in some cases
2728 if Analyzed
(Aspect
) then
2732 -- Skip looking at aspect if it is totally disabled. Just mark it
2733 -- as such for later reference in the tree. This also sets the
2734 -- Is_Ignored and Is_Checked flags appropriately.
2736 Check_Applicable_Policy
(Aspect
);
2738 if Is_Disabled
(Aspect
) then
2742 -- Set the source location of expression, used in the case of
2743 -- a failed precondition/postcondition or invariant. Note that
2744 -- the source location of the expression is not usually the best
2745 -- choice here. For example, it gets located on the last AND
2746 -- keyword in a chain of boolean expressiond AND'ed together.
2747 -- It is best to put the message on the first character of the
2748 -- assertion, which is the effect of the First_Node call here.
2750 if Present
(Expr
) then
2751 Eloc
:= Sloc
(First_Node
(Expr
));
2754 -- Check restriction No_Implementation_Aspect_Specifications
2756 if Implementation_Defined_Aspect
(A_Id
) then
2758 (No_Implementation_Aspect_Specifications
, Aspect
);
2761 -- Check restriction No_Specification_Of_Aspect
2763 Check_Restriction_No_Specification_Of_Aspect
(Aspect
);
2765 -- Mark aspect analyzed (actual analysis is delayed till later)
2767 if A_Id
/= Aspect_User_Aspect
then
2768 -- Analyzed flag is handled differently for a User_Aspect
2769 -- aspect specification because it can also be analyzed
2770 -- "on demand" from Aspects.Find_Aspect. So that analysis
2771 -- tests for the case where the aspect specification has
2772 -- already been analyzed (in which case it just returns)
2773 -- and takes care of calling Set_Analyzed.
2775 Set_Analyzed
(Aspect
);
2778 Set_Entity
(Aspect
, E
);
2780 -- Build the reference to E that will be used in the built pragmas
2782 Ent
:= New_Occurrence_Of
(E
, Sloc
(Id
));
2784 if A_Id
in Aspect_Attach_Handler | Aspect_Interrupt_Handler
then
2786 -- Treat the specification as a reference to the protected
2787 -- operation, which might otherwise appear unreferenced and
2788 -- generate spurious warnings.
2790 Generate_Reference
(E
, Id
);
2793 -- Check for duplicate aspect. Note that the Comes_From_Source
2794 -- test allows duplicate Pre/Post's that we generate internally
2795 -- to escape being flagged here.
2797 if No_Duplicates_Allowed
(A_Id
) then
2799 while Anod
/= Aspect
loop
2800 if Comes_From_Source
(Aspect
)
2801 and then Same_Aspect
(A_Id
, Get_Aspect_Id
(Anod
))
2803 Error_Msg_Name_1
:= Nam
;
2804 Error_Msg_Sloc
:= Sloc
(Anod
);
2806 -- Case of same aspect specified twice
2808 if Class_Present
(Anod
) = Class_Present
(Aspect
) then
2809 if not Class_Present
(Anod
) then
2811 ("aspect% for & previously given#",
2815 ("aspect `%''Class` for & previously given#",
2825 -- Check some general restrictions on language defined aspects
2827 if not Implementation_Defined_Aspect
(A_Id
)
2828 or else A_Id
in Aspect_Async_Readers
2829 | Aspect_Async_Writers
2830 | Aspect_Effective_Reads
2831 | Aspect_Effective_Writes
2832 | Aspect_Preelaborable_Initialization
2834 Error_Msg_Name_1
:= Nam
;
2836 -- Not allowed for renaming declarations. Examine the original
2837 -- node because a subprogram renaming may have been rewritten
2840 if Nkind
(Original_Node
(N
)) in N_Renaming_Declaration
then
2842 ("aspect % not allowed for renaming declaration",
2846 -- Not allowed for formal type declarations in previous
2847 -- versions of the language. Allowed for them only for
2848 -- shared variable control aspects.
2850 -- Original node is used in case expansion rewrote the node -
2851 -- as is the case with generic derived types.
2853 if Nkind
(Original_Node
(N
)) = N_Formal_Type_Declaration
then
2854 if Ada_Version
< Ada_2022
then
2856 ("aspect % not allowed for formal type declaration",
2859 elsif A_Id
not in Aspect_Atomic
2861 | Aspect_Independent
2862 | Aspect_Atomic_Components
2863 | Aspect_Independent_Components
2864 | Aspect_Volatile_Components
2865 | Aspect_Async_Readers
2866 | Aspect_Async_Writers
2867 | Aspect_Effective_Reads
2868 | Aspect_Effective_Writes
2869 | Aspect_Preelaborable_Initialization
2872 ("aspect % not allowed for formal type declaration",
2878 -- Copy expression for later processing by the procedures
2879 -- Check_Aspect_At_[Freeze_Point | End_Of_Declarations]
2881 -- The expression may be a subprogram name, and can
2882 -- be an operator name that appears as a string, but
2883 -- requires its own analysis procedure (see sem_ch6).
2885 if Nkind
(Expr
) = N_Operator_Symbol
then
2886 Set_Expression_Copy
(Aspect
, Expr
);
2888 Set_Expression_Copy
(Aspect
, New_Copy_Tree
(Expr
));
2891 -- Set Delay_Required as appropriate to aspect
2893 case Aspect_Delay
(A_Id
) is
2894 when Always_Delay
=>
2895 -- For Boolean aspects, do not delay if no expression
2897 if A_Id
in Boolean_Aspects | Library_Unit_Aspects
then
2898 Delay_Required
:= Present
(Expr
);
2900 Delay_Required
:= True;
2904 Delay_Required
:= False;
2908 -- For Boolean aspects, do not delay if no expression except
2909 -- for Full_Access_Only because we need to process it after
2910 -- Volatile and Atomic, which can be independently delayed.
2912 if A_Id
in Boolean_Aspects
2913 and then A_Id
/= Aspect_Full_Access_Only
2916 Delay_Required
:= False;
2918 -- For non-Boolean aspects, if the expression has the form
2919 -- of an integer literal, then do not delay, since we know
2920 -- the value cannot change. This optimization catches most
2921 -- rep clause cases.
2923 elsif A_Id
not in Boolean_Aspects
2924 and then Present
(Expr
)
2925 and then Nkind
(Expr
) = N_Integer_Literal
2927 Delay_Required
:= False;
2929 -- For Alignment and various Size aspects, do not delay for
2930 -- an attribute reference whose prefix is Standard, for
2931 -- example Standard'Maximum_Alignment or Standard'Word_Size.
2933 elsif A_Id
in Aspect_Alignment
2934 | Aspect_Component_Size
2935 | Aspect_Object_Size
2938 and then Present
(Expr
)
2939 and then Nkind
(Expr
) = N_Attribute_Reference
2940 and then Nkind
(Prefix
(Expr
)) = N_Identifier
2941 and then Chars
(Prefix
(Expr
)) = Name_Standard
2943 Delay_Required
:= False;
2945 -- All other cases are delayed
2948 Delay_Required
:= True;
2949 Set_Has_Delayed_Rep_Aspects
(E
);
2954 and then (A_Id
= Aspect_Stable_Properties
2955 or else A_Id
= Aspect_Designated_Storage_Model
2956 or else A_Id
= Aspect_Storage_Model_Type
2957 or else A_Id
= Aspect_Aggregate
)
2958 -- ??? It seems like we should do this for all aspects, not
2959 -- just these, but that causes as-yet-undiagnosed regressions.
2962 Set_Has_Delayed_Aspects
(E
);
2963 Set_Is_Delayed_Aspect
(Aspect
);
2966 -- Check 13.1(9.2/5): A representation aspect of a subtype or type
2967 -- shall not be specified (whether by a representation item or an
2968 -- aspect_specification) before the type is completely defined
2971 if Is_Representation_Aspect
(A_Id
)
2972 and then Rep_Item_Too_Early
(E
, N
)
2977 -- Processing based on specific aspect
2980 when Aspect_Unimplemented
=>
2981 null; -- ??? temp for now
2983 -- No_Aspect should be impossible
2986 raise Program_Error
;
2988 -- Case 1: Aspects corresponding to attribute definition
2994 | Aspect_Component_Size
2995 | Aspect_Constant_Indexing
2996 | Aspect_Default_Iterator
2997 | Aspect_Dispatching_Domain
2998 | Aspect_External_Tag
3001 | Aspect_Iterator_Element
3002 | Aspect_Machine_Radix
3003 | Aspect_Object_Size
3007 | Aspect_Scalar_Storage_Order
3008 | Aspect_Simple_Storage_Pool
3011 | Aspect_Storage_Pool
3012 | Aspect_Stream_Size
3014 | Aspect_Variable_Indexing
3017 -- Indexing aspects apply only to tagged type
3019 if A_Id
in Aspect_Constant_Indexing
3020 | Aspect_Variable_Indexing
3021 and then not (Is_Type
(E
)
3022 and then Is_Tagged_Type
(E
))
3025 ("indexing aspect can only apply to a tagged type",
3030 -- For the case of aspect Address, we don't consider that we
3031 -- know the entity is never set in the source, since it is
3032 -- is likely aliasing is occurring.
3034 -- Note: one might think that the analysis of the resulting
3035 -- attribute definition clause would take care of that, but
3036 -- that's not the case since it won't be from source.
3038 if A_Id
= Aspect_Address
then
3039 Set_Never_Set_In_Source
(E
, False);
3042 -- Correctness of the profile of a stream operation is
3043 -- verified at the freeze point, but we must detect the
3044 -- illegal specification of this aspect for a subtype now,
3045 -- to prevent malformed rep_item chains.
3047 if A_Id
in Aspect_Input
3052 if not Is_First_Subtype
(E
) then
3054 ("local name must be a first subtype", Aspect
);
3057 -- If stream aspect applies to the class-wide type,
3058 -- the generated attribute definition applies to the
3059 -- class-wide type as well.
3061 elsif Class_Present
(Aspect
) then
3063 Make_Attribute_Reference
(Loc
,
3065 Attribute_Name
=> Name_Class
);
3069 -- Construct the attribute_definition_clause. The expression
3070 -- in the aspect specification is simply shared with the
3071 -- constructed attribute, because it will be fully analyzed
3072 -- when the attribute is processed.
3075 Make_Attribute_Definition_Clause
(Loc
,
3078 Expression
=> Relocate_Expression
(Expr
));
3080 -- If the address is specified, then we treat the entity as
3081 -- referenced, to avoid spurious warnings. This is analogous
3082 -- to what is done with an attribute definition clause, but
3083 -- here we don't want to generate a reference because this
3084 -- is the point of definition of the entity.
3086 if A_Id
= Aspect_Address
then
3090 -- Case 2: Aspects corresponding to pragmas
3092 -- Case 2a: Aspects corresponding to pragmas with two
3093 -- arguments, where the first argument is a local name
3094 -- referring to the entity, and the second argument is the
3095 -- aspect definition expression.
3099 when Aspect_Linker_Section
=>
3100 Aitem
:= Make_Aitem_Pragma
3101 (Pragma_Argument_Associations
=> New_List
(
3102 Make_Pragma_Argument_Association
(Loc
,
3103 Expression
=> New_Occurrence_Of
(E
, Loc
)),
3104 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3105 Expression
=> Relocate_Node
(Expr
))),
3106 Pragma_Name
=> Name_Linker_Section
);
3108 -- No need to delay the processing if the entity is already
3109 -- frozen. This should only happen for subprogram bodies.
3111 if Is_Frozen
(E
) then
3112 pragma Assert
(Nkind
(N
) = N_Subprogram_Body
);
3113 Delay_Required
:= False;
3118 -- Corresponds to pragma Implemented, construct the pragma
3120 when Aspect_Synchronization
=>
3121 Aitem
:= Make_Aitem_Pragma
3122 (Pragma_Argument_Associations
=> New_List
(
3123 Make_Pragma_Argument_Association
(Loc
,
3124 Expression
=> New_Occurrence_Of
(E
, Loc
)),
3125 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3126 Expression
=> Relocate_Node
(Expr
))),
3127 Pragma_Name
=> Name_Implemented
);
3131 when Aspect_Attach_Handler
=>
3132 Aitem
:= Make_Aitem_Pragma
3133 (Pragma_Argument_Associations
=> New_List
(
3134 Make_Pragma_Argument_Association
(Sloc
(Ent
),
3136 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3137 Expression
=> Relocate_Expression
(Expr
))),
3138 Pragma_Name
=> Name_Attach_Handler
);
3140 -- We need to insert this pragma into the tree to get proper
3141 -- processing and to look valid from a placement viewpoint.
3143 Insert_Pragma
(Aitem
);
3146 -- Dynamic_Predicate, Predicate, Static_Predicate
3148 when Aspect_Dynamic_Predicate
3149 | Aspect_Ghost_Predicate
3151 | Aspect_Static_Predicate
3153 -- These aspects apply only to subtypes
3155 if not Is_Type
(E
) then
3157 ("predicate can only be specified for a subtype",
3161 elsif Is_Incomplete_Type
(E
) then
3163 ("predicate cannot apply to incomplete view", Aspect
);
3165 elsif Is_Generic_Type
(E
) then
3167 ("predicate cannot apply to formal type", Aspect
);
3171 -- Construct the pragma (always a pragma Predicate, with
3172 -- flags recording whether it is static/dynamic). We also
3173 -- set flags recording this in the type itself.
3175 Aitem
:= Make_Aitem_Pragma
3176 (Pragma_Argument_Associations
=> New_List
(
3177 Make_Pragma_Argument_Association
(Sloc
(Ent
),
3179 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3180 Expression
=> Relocate_Expression
(Expr
))),
3181 Pragma_Name
=> Name_Predicate
);
3183 -- Mark type has predicates, and remember what kind of
3184 -- aspect lead to this predicate (we need this to access
3185 -- the right set of check policies later on).
3187 Set_Has_Predicates
(E
);
3189 if A_Id
= Aspect_Dynamic_Predicate
then
3190 Set_Has_Dynamic_Predicate_Aspect
(E
);
3192 -- If the entity has a dynamic predicate, any inherited
3193 -- static predicate becomes dynamic as well, and the
3194 -- predicate function includes the conjunction of both.
3196 Set_Has_Static_Predicate_Aspect
(E
, False);
3198 elsif A_Id
= Aspect_Static_Predicate
then
3199 Set_Has_Static_Predicate_Aspect
(E
);
3200 elsif A_Id
= Aspect_Ghost_Predicate
then
3201 Set_Has_Ghost_Predicate_Aspect
(E
);
3204 -- If the type is private, indicate that its completion
3205 -- has a freeze node, because that is the one that will
3206 -- be visible at freeze time.
3208 if Is_Private_Type
(E
) and then Present
(Full_View
(E
)) then
3209 Set_Has_Predicates
(Full_View
(E
));
3211 if A_Id
= Aspect_Dynamic_Predicate
then
3212 Set_Has_Dynamic_Predicate_Aspect
(Full_View
(E
));
3213 elsif A_Id
= Aspect_Static_Predicate
then
3214 Set_Has_Static_Predicate_Aspect
(Full_View
(E
));
3215 elsif A_Id
= Aspect_Ghost_Predicate
then
3216 Set_Has_Ghost_Predicate_Aspect
(Full_View
(E
));
3219 Set_Has_Delayed_Aspects
(Full_View
(E
));
3220 Ensure_Freeze_Node
(Full_View
(E
));
3222 -- If there is an Underlying_Full_View, also create a
3223 -- freeze node for that one.
3225 if Is_Private_Type
(Full_View
(E
)) then
3227 U_Full
: constant Entity_Id
:=
3228 Underlying_Full_View
(Full_View
(E
));
3230 if Present
(U_Full
) then
3231 Set_Has_Delayed_Aspects
(U_Full
);
3232 Ensure_Freeze_Node
(U_Full
);
3238 -- Predicate_Failure
3240 when Aspect_Predicate_Failure
=>
3242 -- This aspect applies only to subtypes
3244 if not Is_Type
(E
) then
3246 ("predicate can only be specified for a subtype",
3250 elsif Is_Incomplete_Type
(E
) then
3252 ("predicate cannot apply to incomplete view", Aspect
);
3255 elsif not Has_Predicates
(E
) then
3257 ("Predicate_Failure requires previous predicate" &
3258 " specification", Aspect
);
3261 elsif not (Directly_Specified
(E
, Aspect_Dynamic_Predicate
)
3262 or else Directly_Specified
(E
, Aspect_Predicate
)
3263 or else Directly_Specified
(E
, Aspect_Ghost_Predicate
)
3264 or else Directly_Specified
(E
, Aspect_Static_Predicate
))
3267 ("Predicate_Failure requires accompanying" &
3268 " noninherited predicate specification", Aspect
);
3272 -- Construct the pragma
3274 Aitem
:= Make_Aitem_Pragma
3275 (Pragma_Argument_Associations
=> New_List
(
3276 Make_Pragma_Argument_Association
(Sloc
(Ent
),
3278 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3279 Expression
=> Relocate_Node
(Expr
))),
3280 Pragma_Name
=> Name_Predicate_Failure
);
3282 -- Case 2b: Aspects corresponding to pragmas with two
3283 -- arguments, where the second argument is a local name
3284 -- referring to the entity, and the first argument is the
3285 -- aspect definition expression.
3289 when Aspect_Convention
=>
3290 Analyze_Aspect_Convention
;
3293 -- External_Name, Link_Name
3295 when Aspect_External_Name
3298 Analyze_Aspect_External_Link_Name
;
3301 -- CPU, Interrupt_Priority, Priority
3303 -- These three aspects can be specified for a subprogram spec
3304 -- or body, in which case we analyze the expression and export
3305 -- the value of the aspect.
3307 -- Previously, we generated an equivalent pragma for bodies
3308 -- (note that the specs cannot contain these pragmas). The
3309 -- pragma was inserted ahead of local declarations, rather than
3310 -- after the body. This leads to a certain duplication between
3311 -- the processing performed for the aspect and the pragma, but
3312 -- given the straightforward handling required it is simpler
3313 -- to duplicate than to translate the aspect in the spec into
3314 -- a pragma in the declarative part of the body.
3317 | Aspect_Interrupt_Priority
3320 -- Verify the expression is static when Static_Priorities is
3323 if not Is_OK_Static_Expression
(Expr
) then
3324 Check_Restriction
(Static_Priorities
, Expr
);
3327 if Nkind
(N
) in N_Subprogram_Body | N_Subprogram_Declaration
3329 -- Analyze the aspect expression
3331 Analyze_And_Resolve
(Expr
, Standard_Integer
);
3333 -- Interrupt_Priority aspect not allowed for main
3334 -- subprograms. RM D.1 does not forbid this explicitly,
3335 -- but RM J.15.11(6/3) does not permit pragma
3336 -- Interrupt_Priority for subprograms.
3338 if A_Id
= Aspect_Interrupt_Priority
then
3340 ("Interrupt_Priority aspect cannot apply to "
3341 & "subprogram", Expr
);
3343 -- The expression must be static
3345 elsif not Is_OK_Static_Expression
(Expr
) then
3346 Flag_Non_Static_Expr
3347 ("aspect requires static expression!", Expr
);
3349 -- Check whether this is the main subprogram. Issue a
3350 -- warning only if it is obviously not a main program
3351 -- (when it has parameters or when the subprogram is
3352 -- within a package).
3354 elsif Present
(Parameter_Specifications
3355 (Specification
(N
)))
3356 or else not Is_Compilation_Unit
(Defining_Entity
(N
))
3358 -- See RM D.1(14/3) and D.16(12/3)
3361 ("aspect applied to subprogram other than the "
3362 & "main subprogram has no effect??", Expr
);
3364 -- Otherwise check in range and export the value
3366 -- For the CPU aspect
3368 elsif A_Id
= Aspect_CPU
then
3369 if Is_In_Range
(Expr
, RTE
(RE_CPU_Range
)) then
3371 -- Value is correct so we export the value to make
3372 -- it available at execution time.
3375 (Main_Unit
, UI_To_Int
(Expr_Value
(Expr
)));
3379 ("main subprogram 'C'P'U is out of range", Expr
);
3382 -- For the Priority aspect
3384 elsif A_Id
= Aspect_Priority
then
3385 if Is_In_Range
(Expr
, RTE
(RE_Priority
)) then
3387 -- Value is correct so we export the value to make
3388 -- it available at execution time.
3391 (Main_Unit
, UI_To_Int
(Expr_Value
(Expr
)));
3393 -- Ignore pragma if Relaxed_RM_Semantics to support
3394 -- other targets/non GNAT compilers.
3396 elsif not Relaxed_RM_Semantics
then
3398 ("main subprogram priority is out of range",
3403 -- Load an arbitrary entity from System.Tasking.Stages
3404 -- or System.Tasking.Restricted.Stages (depending on
3405 -- the supported profile) to make sure that one of these
3406 -- packages is implicitly with'ed, since we need to have
3407 -- the tasking run time active for the pragma Priority to
3408 -- have any effect. Previously we with'ed the package
3409 -- System.Tasking, but this package does not trigger the
3410 -- required initialization of the run-time library.
3412 if Restricted_Profile
then
3413 Discard_Node
(RTE
(RE_Activate_Restricted_Tasks
));
3415 Discard_Node
(RTE
(RE_Activate_Tasks
));
3418 -- Handling for these aspects in subprograms is complete
3422 -- For task and protected types pass the aspect as an
3427 Make_Attribute_Definition_Clause
(Loc
,
3430 Expression
=> Relocate_Expression
(Expr
));
3433 -- Suppress/Unsuppress
3435 when Aspect_Suppress
3438 Aitem
:= Make_Aitem_Pragma
3439 (Pragma_Argument_Associations
=> New_List
(
3440 Make_Pragma_Argument_Association
(Loc
,
3441 Expression
=> Relocate_Node
(Expr
)),
3442 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3443 Expression
=> New_Occurrence_Of
(E
, Loc
))),
3444 Pragma_Name
=> Nam
);
3446 Delay_Required
:= False;
3450 when Aspect_Warnings
=>
3451 Aitem
:= Make_Aitem_Pragma
3452 (Pragma_Argument_Associations
=> New_List
(
3453 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3454 Expression
=> Relocate_Node
(Expr
)),
3455 Make_Pragma_Argument_Association
(Loc
,
3456 Expression
=> New_Occurrence_Of
(E
, Loc
))),
3457 Pragma_Name
=> Name_Warnings
);
3459 Decorate
(Aspect
, Aitem
);
3460 Insert_Pragma
(Aitem
);
3463 -- Case 2c: Aspects corresponding to pragmas with three
3466 -- Invariant aspects have a first argument that references the
3467 -- entity, a second argument that is the expression and a third
3468 -- argument that is an appropriate message.
3470 -- Invariant, Type_Invariant
3472 when Aspect_Invariant
3473 | Aspect_Type_Invariant
3475 -- Analysis of the pragma will verify placement legality:
3476 -- an invariant must apply to a private type, or appear in
3477 -- the private part of a spec and apply to a completion.
3479 Aitem
:= Make_Aitem_Pragma
3480 (Pragma_Argument_Associations
=> New_List
(
3481 Make_Pragma_Argument_Association
(Sloc
(Ent
),
3483 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3484 Expression
=> Relocate_Node
(Expr
))),
3485 Pragma_Name
=> Name_Invariant
);
3487 -- Add message unless exception messages are suppressed
3489 if not Opt
.Exception_Locations_Suppressed
then
3490 Append_To
(Pragma_Argument_Associations
(Aitem
),
3491 Make_Pragma_Argument_Association
(Eloc
,
3492 Chars
=> Name_Message
,
3494 Make_String_Literal
(Eloc
,
3495 Strval
=> "failed invariant from "
3496 & Build_Location_String
(Eloc
))));
3499 -- For Invariant case, insert immediately after the entity
3500 -- declaration. We do not have to worry about delay issues
3501 -- since the pragma processing takes care of this.
3503 Delay_Required
:= False;
3505 -- Case 2d : Aspects that correspond to a pragma with one
3510 -- Aspect Abstract_State introduces implicit declarations for
3511 -- all state abstraction entities it defines. To emulate this
3512 -- behavior, insert the pragma at the beginning of the visible
3513 -- declarations of the related package so that it is analyzed
3516 when Aspect_Abstract_State
=> Abstract_State
: declare
3517 Context
: Node_Id
:= N
;
3520 -- When aspect Abstract_State appears on a generic package,
3521 -- it is propagated to the package instance. The context in
3522 -- this case is the instance spec.
3524 if Nkind
(Context
) = N_Package_Instantiation
then
3525 Context
:= Instance_Spec
(Context
);
3528 if Nkind
(Context
) in N_Generic_Package_Declaration
3529 | N_Package_Declaration
3531 Aitem
:= Make_Aitem_Pragma
3532 (Pragma_Argument_Associations
=> New_List
(
3533 Make_Pragma_Argument_Association
(Loc
,
3534 Expression
=> Relocate_Node
(Expr
))),
3535 Pragma_Name
=> Name_Abstract_State
);
3537 Decorate
(Aspect
, Aitem
);
3541 Is_Generic_Instance
(Defining_Entity
(Context
)));
3545 ("aspect & must apply to a package declaration",
3552 -- Aspect Async_Readers is never delayed because it is
3553 -- equivalent to a source pragma which appears after the
3554 -- related object declaration.
3556 when Aspect_Async_Readers
=>
3557 Aitem
:= Make_Aitem_Pragma
3558 (Pragma_Argument_Associations
=> New_List
(
3559 Make_Pragma_Argument_Association
(Loc
,
3560 Expression
=> Relocate_Node
(Expr
))),
3561 Pragma_Name
=> Name_Async_Readers
);
3563 Decorate
(Aspect
, Aitem
);
3564 Insert_Pragma
(Aitem
);
3567 -- Aspect Async_Writers is never delayed because it is
3568 -- equivalent to a source pragma which appears after the
3569 -- related object declaration.
3571 when Aspect_Async_Writers
=>
3572 Aitem
:= Make_Aitem_Pragma
3573 (Pragma_Argument_Associations
=> New_List
(
3574 Make_Pragma_Argument_Association
(Loc
,
3575 Expression
=> Relocate_Node
(Expr
))),
3576 Pragma_Name
=> Name_Async_Writers
);
3578 Decorate
(Aspect
, Aitem
);
3579 Insert_Pragma
(Aitem
);
3582 -- Aspect Constant_After_Elaboration is never delayed because
3583 -- it is equivalent to a source pragma which appears after the
3584 -- related object declaration.
3586 when Aspect_Constant_After_Elaboration
=>
3587 Aitem
:= Make_Aitem_Pragma
3588 (Pragma_Argument_Associations
=> New_List
(
3589 Make_Pragma_Argument_Association
(Loc
,
3590 Expression
=> Relocate_Node
(Expr
))),
3592 Name_Constant_After_Elaboration
);
3594 Decorate
(Aspect
, Aitem
);
3595 Insert_Pragma
(Aitem
);
3598 -- Aspect Default_Internal_Condition is never delayed because
3599 -- it is equivalent to a source pragma which appears after the
3600 -- related private type. To deal with forward references, the
3601 -- generated pragma is stored in the rep chain of the related
3602 -- private type as types do not carry contracts. The pragma is
3603 -- wrapped inside of a procedure at the freeze point of the
3604 -- private type's full view.
3606 -- A type entity argument is appended to facilitate inheriting
3607 -- the aspect from parent types (see Build_DIC_Procedure_Body),
3608 -- though that extra argument isn't documented for the pragma.
3610 when Aspect_Default_Initial_Condition
=>
3611 Aitem
:= Make_Aitem_Pragma
3612 (Pragma_Argument_Associations
=> New_List
(
3613 Make_Pragma_Argument_Association
(Loc
,
3614 Expression
=> Relocate_Node
(Expr
)),
3615 Make_Pragma_Argument_Association
(Sloc
(Ent
),
3616 Expression
=> Ent
)),
3618 Name_Default_Initial_Condition
);
3620 Decorate
(Aspect
, Aitem
);
3621 Insert_Pragma
(Aitem
);
3624 -- Default_Storage_Pool
3626 when Aspect_Default_Storage_Pool
=>
3627 Aitem
:= Make_Aitem_Pragma
3628 (Pragma_Argument_Associations
=> New_List
(
3629 Make_Pragma_Argument_Association
(Loc
,
3630 Expression
=> Relocate_Node
(Expr
))),
3632 Name_Default_Storage_Pool
);
3634 Decorate
(Aspect
, Aitem
);
3635 Insert_Pragma
(Aitem
);
3640 -- Aspect Depends is never delayed because it is equivalent to
3641 -- a source pragma which appears after the related subprogram.
3642 -- To deal with forward references, the generated pragma is
3643 -- stored in the contract of the related subprogram and later
3644 -- analyzed at the end of the declarative region. See routine
3645 -- Analyze_Depends_In_Decl_Part for details.
3647 when Aspect_Depends
=>
3648 Aitem
:= Make_Aitem_Pragma
3649 (Pragma_Argument_Associations
=> New_List
(
3650 Make_Pragma_Argument_Association
(Loc
,
3651 Expression
=> Relocate_Node
(Expr
))),
3652 Pragma_Name
=> Name_Depends
);
3654 Decorate
(Aspect
, Aitem
);
3655 Insert_Pragma
(Aitem
);
3658 -- Aspect Effective_Reads is never delayed because it is
3659 -- equivalent to a source pragma which appears after the
3660 -- related object declaration.
3662 when Aspect_Effective_Reads
=>
3663 Aitem
:= Make_Aitem_Pragma
3664 (Pragma_Argument_Associations
=> New_List
(
3665 Make_Pragma_Argument_Association
(Loc
,
3666 Expression
=> Relocate_Node
(Expr
))),
3667 Pragma_Name
=> Name_Effective_Reads
);
3669 Decorate
(Aspect
, Aitem
);
3670 Insert_Pragma
(Aitem
);
3673 -- Aspect Effective_Writes is never delayed because it is
3674 -- equivalent to a source pragma which appears after the
3675 -- related object declaration.
3677 when Aspect_Effective_Writes
=>
3678 Aitem
:= Make_Aitem_Pragma
3679 (Pragma_Argument_Associations
=> New_List
(
3680 Make_Pragma_Argument_Association
(Loc
,
3681 Expression
=> Relocate_Node
(Expr
))),
3682 Pragma_Name
=> Name_Effective_Writes
);
3684 Decorate
(Aspect
, Aitem
);
3685 Insert_Pragma
(Aitem
);
3688 -- Aspect Extensions_Visible is never delayed because it is
3689 -- equivalent to a source pragma which appears after the
3690 -- related subprogram.
3692 when Aspect_Extensions_Visible
=>
3693 Aitem
:= Make_Aitem_Pragma
3694 (Pragma_Argument_Associations
=> New_List
(
3695 Make_Pragma_Argument_Association
(Loc
,
3696 Expression
=> Relocate_Node
(Expr
))),
3697 Pragma_Name
=> Name_Extensions_Visible
);
3699 Decorate
(Aspect
, Aitem
);
3700 Insert_Pragma
(Aitem
);
3703 -- Aspect Ghost is never delayed because it is equivalent to a
3704 -- source pragma which appears at the top of [generic] package
3705 -- declarations or after an object, a [generic] subprogram, or
3706 -- a type declaration.
3708 when Aspect_Ghost
=>
3709 Aitem
:= Make_Aitem_Pragma
3710 (Pragma_Argument_Associations
=> New_List
(
3711 Make_Pragma_Argument_Association
(Loc
,
3712 Expression
=> Relocate_Node
(Expr
))),
3713 Pragma_Name
=> Name_Ghost
);
3715 Decorate
(Aspect
, Aitem
);
3716 Insert_Pragma
(Aitem
);
3721 -- Aspect Global is never delayed because it is equivalent to
3722 -- a source pragma which appears after the related subprogram.
3723 -- To deal with forward references, the generated pragma is
3724 -- stored in the contract of the related subprogram and later
3725 -- analyzed at the end of the declarative region. See routine
3726 -- Analyze_Global_In_Decl_Part for details.
3728 when Aspect_Global
=>
3729 Aitem
:= Make_Aitem_Pragma
3730 (Pragma_Argument_Associations
=> New_List
(
3731 Make_Pragma_Argument_Association
(Loc
,
3732 Expression
=> Relocate_Node
(Expr
))),
3733 Pragma_Name
=> Name_Global
);
3735 Decorate
(Aspect
, Aitem
);
3736 Insert_Pragma
(Aitem
);
3739 -- Initial_Condition
3741 -- Aspect Initial_Condition is never delayed because it is
3742 -- equivalent to a source pragma which appears after the
3743 -- related package. To deal with forward references, the
3744 -- generated pragma is stored in the contract of the related
3745 -- package and later analyzed at the end of the declarative
3746 -- region. See routine Analyze_Initial_Condition_In_Decl_Part
3749 when Aspect_Initial_Condition
=> Initial_Condition
: declare
3750 Context
: Node_Id
:= N
;
3753 -- When aspect Initial_Condition appears on a generic
3754 -- package, it is propagated to the package instance. The
3755 -- context in this case is the instance spec.
3757 if Nkind
(Context
) = N_Package_Instantiation
then
3758 Context
:= Instance_Spec
(Context
);
3761 if Nkind
(Context
) in N_Generic_Package_Declaration
3762 | N_Package_Declaration
3764 Aitem
:= Make_Aitem_Pragma
3765 (Pragma_Argument_Associations
=> New_List
(
3766 Make_Pragma_Argument_Association
(Loc
,
3767 Expression
=> Relocate_Node
(Expr
))),
3769 Name_Initial_Condition
);
3771 Decorate
(Aspect
, Aitem
);
3775 Is_Generic_Instance
(Defining_Entity
(Context
)));
3777 -- Otherwise the context is illegal
3781 ("aspect & must apply to a package declaration",
3786 end Initial_Condition
;
3790 -- Aspect Initializes is never delayed because it is equivalent
3791 -- to a source pragma appearing after the related package. To
3792 -- deal with forward references, the generated pragma is stored
3793 -- in the contract of the related package and later analyzed at
3794 -- the end of the declarative region. For details, see routine
3795 -- Analyze_Initializes_In_Decl_Part.
3797 when Aspect_Initializes
=> Initializes
: declare
3798 Context
: Node_Id
:= N
;
3801 -- When aspect Initializes appears on a generic package,
3802 -- it is propagated to the package instance. The context
3803 -- in this case is the instance spec.
3805 if Nkind
(Context
) = N_Package_Instantiation
then
3806 Context
:= Instance_Spec
(Context
);
3809 if Nkind
(Context
) in N_Generic_Package_Declaration
3810 | N_Package_Declaration
3812 Aitem
:= Make_Aitem_Pragma
3813 (Pragma_Argument_Associations
=> New_List
(
3814 Make_Pragma_Argument_Association
(Loc
,
3815 Expression
=> Relocate_Node
(Expr
))),
3816 Pragma_Name
=> Name_Initializes
);
3818 Decorate
(Aspect
, Aitem
);
3822 Is_Generic_Instance
(Defining_Entity
(Context
)));
3824 -- Otherwise the context is illegal
3828 ("aspect & must apply to a package declaration",
3835 -- Max_Entry_Queue_Depth
3837 when Aspect_Max_Entry_Queue_Depth
=>
3838 Aitem
:= Make_Aitem_Pragma
3839 (Pragma_Argument_Associations
=> New_List
(
3840 Make_Pragma_Argument_Association
(Loc
,
3841 Expression
=> Relocate_Node
(Expr
))),
3842 Pragma_Name
=> Name_Max_Entry_Queue_Depth
);
3844 Decorate
(Aspect
, Aitem
);
3845 Insert_Pragma
(Aitem
);
3848 -- Max_Entry_Queue_Length
3850 when Aspect_Max_Entry_Queue_Length
=>
3851 Aitem
:= Make_Aitem_Pragma
3852 (Pragma_Argument_Associations
=> New_List
(
3853 Make_Pragma_Argument_Association
(Loc
,
3854 Expression
=> Relocate_Node
(Expr
))),
3855 Pragma_Name
=> Name_Max_Entry_Queue_Length
);
3857 Decorate
(Aspect
, Aitem
);
3858 Insert_Pragma
(Aitem
);
3863 when Aspect_Max_Queue_Length
=>
3864 Aitem
:= Make_Aitem_Pragma
3865 (Pragma_Argument_Associations
=> New_List
(
3866 Make_Pragma_Argument_Association
(Loc
,
3867 Expression
=> Relocate_Node
(Expr
))),
3868 Pragma_Name
=> Name_Max_Queue_Length
);
3870 Decorate
(Aspect
, Aitem
);
3871 Insert_Pragma
(Aitem
);
3874 -- Aspect No_Caching is never delayed because it is equivalent
3875 -- to a source pragma which appears after the related object
3878 when Aspect_No_Caching
=>
3879 Aitem
:= Make_Aitem_Pragma
3880 (Pragma_Argument_Associations
=> New_List
(
3881 Make_Pragma_Argument_Association
(Loc
,
3882 Expression
=> Relocate_Node
(Expr
))),
3883 Pragma_Name
=> Name_No_Caching
);
3885 Decorate
(Aspect
, Aitem
);
3886 Insert_Pragma
(Aitem
);
3889 -- No_Controlled_Parts, No_Task_Parts
3891 when Aspect_No_Controlled_Parts | Aspect_No_Task_Parts
=>
3893 -- Check appropriate type argument
3895 if not Is_Type
(E
) then
3897 ("aspect % can only be applied to types", E
);
3900 -- Disallow subtypes
3902 if Nkind
(Declaration_Node
(E
)) = N_Subtype_Declaration
then
3904 ("aspect % cannot be applied to subtypes", E
);
3907 -- Resolve the expression to a boolean
3909 if Present
(Expr
) then
3910 Check_Expr_Is_OK_Static_Expression
(Expr
, Any_Boolean
);
3917 when Aspect_Obsolescent
=> declare
3925 Make_Pragma_Argument_Association
(Sloc
(Expr
),
3926 Expression
=> Relocate_Node
(Expr
)));
3929 Aitem
:= Make_Aitem_Pragma
3930 (Pragma_Argument_Associations
=> Args
,
3931 Pragma_Name
=> Name_Obsolescent
);
3936 when Aspect_Part_Of
=>
3937 if Nkind
(N
) in N_Object_Declaration
3938 | N_Package_Instantiation
3939 or else Is_Single_Concurrent_Type_Declaration
(N
)
3941 Aitem
:= Make_Aitem_Pragma
3942 (Pragma_Argument_Associations
=> New_List
(
3943 Make_Pragma_Argument_Association
(Loc
,
3944 Expression
=> Relocate_Node
(Expr
))),
3945 Pragma_Name
=> Name_Part_Of
);
3947 Decorate
(Aspect
, Aitem
);
3948 Insert_Pragma
(Aitem
);
3952 ("aspect & must apply to package instantiation, "
3953 & "object, single protected type or single task type",
3959 -- Aspect Side_Effects is never delayed because it is
3960 -- equivalent to a source pragma which appears after
3961 -- the related subprogram.
3963 when Aspect_Side_Effects
=>
3964 Aitem
:= Make_Aitem_Pragma
3965 (Pragma_Argument_Associations
=> New_List
(
3966 Make_Pragma_Argument_Association
(Loc
,
3967 Expression
=> Relocate_Node
(Expr
))),
3968 Pragma_Name
=> Name_Side_Effects
);
3970 Decorate
(Aspect
, Aitem
);
3971 Insert_Pragma
(Aitem
);
3976 when Aspect_SPARK_Mode
=>
3977 Aitem
:= Make_Aitem_Pragma
3978 (Pragma_Argument_Associations
=> New_List
(
3979 Make_Pragma_Argument_Association
(Loc
,
3980 Expression
=> Relocate_Node
(Expr
))),
3981 Pragma_Name
=> Name_SPARK_Mode
);
3983 Decorate
(Aspect
, Aitem
);
3984 Insert_Pragma
(Aitem
);
3989 -- Aspect Refined_Depends is never delayed because it is
3990 -- equivalent to a source pragma which appears in the
3991 -- declarations of the related subprogram body. To deal with
3992 -- forward references, the generated pragma is stored in the
3993 -- contract of the related subprogram body and later analyzed
3994 -- at the end of the declarative region. For details, see
3995 -- routine Analyze_Refined_Depends_In_Decl_Part.
3997 when Aspect_Refined_Depends
=>
3998 Aitem
:= Make_Aitem_Pragma
3999 (Pragma_Argument_Associations
=> New_List
(
4000 Make_Pragma_Argument_Association
(Loc
,
4001 Expression
=> Relocate_Node
(Expr
))),
4002 Pragma_Name
=> Name_Refined_Depends
);
4004 Decorate
(Aspect
, Aitem
);
4005 Insert_Pragma
(Aitem
);
4010 -- Aspect Refined_Global is never delayed because it is
4011 -- equivalent to a source pragma which appears in the
4012 -- declarations of the related subprogram body. To deal with
4013 -- forward references, the generated pragma is stored in the
4014 -- contract of the related subprogram body and later analyzed
4015 -- at the end of the declarative region. For details, see
4016 -- routine Analyze_Refined_Global_In_Decl_Part.
4018 when Aspect_Refined_Global
=>
4019 Aitem
:= Make_Aitem_Pragma
4020 (Pragma_Argument_Associations
=> New_List
(
4021 Make_Pragma_Argument_Association
(Loc
,
4022 Expression
=> Relocate_Node
(Expr
))),
4023 Pragma_Name
=> Name_Refined_Global
);
4025 Decorate
(Aspect
, Aitem
);
4026 Insert_Pragma
(Aitem
);
4031 when Aspect_Refined_Post
=>
4032 Aitem
:= Make_Aitem_Pragma
4033 (Pragma_Argument_Associations
=> New_List
(
4034 Make_Pragma_Argument_Association
(Loc
,
4035 Expression
=> Relocate_Node
(Expr
))),
4036 Pragma_Name
=> Name_Refined_Post
);
4038 Decorate
(Aspect
, Aitem
);
4039 Insert_Pragma
(Aitem
);
4044 when Aspect_Refined_State
=>
4046 -- The corresponding pragma for Refined_State is inserted in
4047 -- the declarations of the related package body. This action
4048 -- synchronizes both the source and from-aspect versions of
4051 if Nkind
(N
) = N_Package_Body
then
4052 Aitem
:= Make_Aitem_Pragma
4053 (Pragma_Argument_Associations
=> New_List
(
4054 Make_Pragma_Argument_Association
(Loc
,
4055 Expression
=> Relocate_Node
(Expr
))),
4056 Pragma_Name
=> Name_Refined_State
);
4058 Decorate
(Aspect
, Aitem
);
4059 Insert_Pragma
(Aitem
);
4061 -- Otherwise the context is illegal
4065 ("aspect & must apply to a package body", Aspect
, Id
);
4070 -- Relative_Deadline
4072 when Aspect_Relative_Deadline
=>
4073 Aitem
:= Make_Aitem_Pragma
4074 (Pragma_Argument_Associations
=> New_List
(
4075 Make_Pragma_Argument_Association
(Loc
,
4076 Expression
=> Relocate_Node
(Expr
))),
4077 Pragma_Name
=> Name_Relative_Deadline
);
4079 -- If the aspect applies to a task, the corresponding pragma
4080 -- must appear within its declarations, not after.
4082 if Nkind
(N
) = N_Task_Type_Declaration
then
4088 if No
(Task_Definition
(N
)) then
4089 Set_Task_Definition
(N
,
4090 Make_Task_Definition
(Loc
,
4091 Visible_Declarations
=> New_List
,
4092 End_Label
=> Empty
));
4095 Def
:= Task_Definition
(N
);
4096 V
:= Visible_Declarations
(Def
);
4097 if not Is_Empty_List
(V
) then
4098 Insert_Before
(First
(V
), Aitem
);
4101 Set_Visible_Declarations
(Def
, New_List
(Aitem
));
4108 -- Relaxed_Initialization
4110 when Aspect_Relaxed_Initialization
=>
4111 Analyze_Aspect_Relaxed_Initialization
;
4114 -- Secondary_Stack_Size
4116 -- Aspect Secondary_Stack_Size needs to be converted into a
4117 -- pragma for two reasons: the attribute is not analyzed until
4118 -- after the expansion of the task type declaration and the
4119 -- attribute does not have visibility on the discriminant.
4121 when Aspect_Secondary_Stack_Size
=>
4122 Aitem
:= Make_Aitem_Pragma
4123 (Pragma_Argument_Associations
=> New_List
(
4124 Make_Pragma_Argument_Association
(Loc
,
4125 Expression
=> Relocate_Node
(Expr
))),
4127 Name_Secondary_Stack_Size
);
4129 Decorate
(Aspect
, Aitem
);
4130 Insert_Pragma
(Aitem
);
4135 when Aspect_User_Aspect
=>
4136 Analyze_User_Aspect_Aspect_Specification
(Aspect
);
4139 -- Volatile_Function
4141 -- Aspect Volatile_Function is never delayed because it is
4142 -- equivalent to a source pragma which appears after the
4143 -- related subprogram.
4145 when Aspect_Volatile_Function
=>
4146 Aitem
:= Make_Aitem_Pragma
4147 (Pragma_Argument_Associations
=> New_List
(
4148 Make_Pragma_Argument_Association
(Loc
,
4149 Expression
=> Relocate_Node
(Expr
))),
4150 Pragma_Name
=> Name_Volatile_Function
);
4152 Decorate
(Aspect
, Aitem
);
4153 Insert_Pragma
(Aitem
);
4156 -- Case 2e: Annotate aspect
4158 when Aspect_Annotate | Aspect_GNAT_Annotate
=>
4165 -- The argument can be a single identifier
4167 if Nkind
(Expr
) = N_Identifier
then
4169 -- One level of parens is allowed
4171 if Paren_Count
(Expr
) > 1 then
4172 Error_Msg_F
("extra parentheses ignored", Expr
);
4175 Set_Paren_Count
(Expr
, 0);
4177 -- Add the single item to the list
4179 Args
:= New_List
(Expr
);
4181 -- Otherwise we must have an aggregate
4183 elsif Nkind
(Expr
) = N_Aggregate
then
4185 -- Must be positional
4187 if Present
(Component_Associations
(Expr
)) then
4189 ("purely positional aggregate required", Expr
);
4193 -- Must not be parenthesized
4195 if Paren_Count
(Expr
) /= 0 then
4196 Error_Msg_F
-- CODEFIX
4197 ("redundant parentheses", Expr
);
4200 -- List of arguments is list of aggregate expressions
4202 Args
:= Expressions
(Expr
);
4204 -- Anything else is illegal
4207 Error_Msg_F
("wrong form for Annotate aspect", Expr
);
4211 -- Prepare pragma arguments
4214 Arg
:= First
(Args
);
4215 while Present
(Arg
) loop
4217 Make_Pragma_Argument_Association
(Sloc
(Arg
),
4218 Expression
=> Relocate_Node
(Arg
)));
4223 Make_Pragma_Argument_Association
(Sloc
(Ent
),
4224 Chars
=> Name_Entity
,
4225 Expression
=> Ent
));
4227 Aitem
:= Make_Aitem_Pragma
4228 (Pragma_Argument_Associations
=> Pargs
,
4229 Pragma_Name
=> Name_Annotate
);
4232 -- Case 3 : Aspects that don't correspond to pragma/attribute
4233 -- definition clause.
4235 -- Case 3a: The aspects listed below don't correspond to
4236 -- pragmas/attributes but do require delayed analysis.
4238 when Aspect_Default_Value | Aspect_Default_Component_Value
=>
4239 Error_Msg_Name_1
:= Nam
;
4241 if not Is_Type
(E
) then
4242 Error_Msg_N
("aspect% can only apply to a type", Id
);
4245 elsif not Is_First_Subtype
(E
) then
4246 Error_Msg_N
("aspect% cannot apply to subtype", Id
);
4249 elsif A_Id
= Aspect_Default_Value
4250 and then not Is_Scalar_Type
(E
)
4253 ("aspect% can only be applied to scalar type", Id
);
4256 elsif A_Id
= Aspect_Default_Component_Value
then
4257 if not Is_Array_Type
(E
) then
4259 ("aspect% can only be applied to array type", Id
);
4262 elsif not Is_Scalar_Type
(Component_Type
(E
)) then
4263 Error_Msg_N
("aspect% requires scalar components", Id
);
4270 when Aspect_Aggregate
=>
4271 -- We will be checking that the aspect is not specified on a
4272 -- non-array type in Check_Aspect_At_Freeze_Point
4274 Validate_Aspect_Aggregate
(Expr
);
4275 Record_Rep_Item
(E
, Aspect
);
4278 when Aspect_Local_Restrictions
=>
4279 Validate_Aspect_Local_Restrictions
(E
, Expr
);
4280 Record_Rep_Item
(E
, Aspect
);
4283 when Aspect_Stable_Properties
=>
4284 Validate_Aspect_Stable_Properties
4285 (E
, Expr
, Class_Present
=> Class_Present
(Aspect
));
4286 Record_Rep_Item
(E
, Aspect
);
4289 when Aspect_Designated_Storage_Model
=>
4290 if not All_Extensions_Allowed
then
4291 Error_Msg_GNAT_Extension
("aspect %", Sloc
(Aspect
));
4293 elsif not Is_Type
(E
)
4294 or else Ekind
(E
) /= E_Access_Type
4297 ("can only be specified for pool-specific access type",
4301 Record_Rep_Item
(E
, Aspect
);
4304 when Aspect_Storage_Model_Type
=>
4305 if not All_Extensions_Allowed
then
4306 Error_Msg_GNAT_Extension
("aspect %", Sloc
(Aspect
));
4308 elsif not Is_Type
(E
)
4309 or else not Is_Immutably_Limited_Type
(E
)
4312 ("can only be specified for immutably limited type",
4316 Record_Rep_Item
(E
, Aspect
);
4319 when Aspect_Integer_Literal
4320 | Aspect_Real_Literal
4321 | Aspect_String_Literal
4324 if not Is_First_Subtype
(E
) then
4326 ("may only be specified for a first subtype", Aspect
);
4330 if Ada_Version
< Ada_2022
then
4332 (No_Implementation_Aspect_Specifications
, N
);
4337 -- Case 3b: The aspects listed below don't correspond to
4338 -- pragmas/attributes and don't need delayed analysis.
4340 -- Implicit_Dereference
4342 -- For Implicit_Dereference, External_Name and Link_Name, only
4343 -- the legality checks are done during the analysis, thus no
4344 -- delay is required.
4346 when Aspect_Implicit_Dereference
=>
4347 Analyze_Aspect_Implicit_Dereference
;
4352 when Aspect_Dimension
=>
4353 Analyze_Aspect_Dimension
(N
, Id
, Expr
);
4358 when Aspect_Dimension_System
=>
4359 Analyze_Aspect_Dimension_System
(N
, Id
, Expr
);
4362 -- Case 4: Aspects requiring special handling
4364 -- Pre/Post/Test_Case/Contract_Cases/Always_Terminates/
4365 -- Exceptional_Cases and Subprogram_Variant whose corresponding
4366 -- pragmas take care of the delay.
4370 -- Aspects Pre/Post generate Precondition/Postcondition pragmas
4371 -- with a first argument that is the expression, and a second
4372 -- argument that is an informative message if the test fails.
4373 -- This is inserted right after the declaration, to get the
4374 -- required pragma placement. The processing for the pragmas
4375 -- takes care of the required delay.
4377 when Pre_Post_Aspects
=> Pre_Post
: declare
4381 if A_Id
in Aspect_Pre | Aspect_Precondition
then
4382 Pname
:= Name_Precondition
;
4384 Pname
:= Name_Postcondition
;
4387 -- Check that the class-wide predicate cannot be applied to
4388 -- an operation of a synchronized type. AI12-0182 forbids
4389 -- these altogether, while earlier language semantics made
4390 -- them legal on tagged synchronized types.
4392 -- Other legality checks are performed when analyzing the
4393 -- contract of the operation.
4395 if Class_Present
(Aspect
)
4396 and then Is_Concurrent_Type
(Current_Scope
)
4397 and then Ekind
(E
) in E_Entry | E_Function | E_Procedure
4399 Error_Msg_Name_1
:= Original_Aspect_Pragma_Name
(Aspect
);
4401 ("aspect % can only be specified for a primitive "
4402 & "operation of a tagged type", Aspect
);
4407 -- Remember class-wide conditions; they will be merged
4408 -- with inherited conditions.
4410 if Class_Present
(Aspect
)
4411 and then A_Id
in Aspect_Pre | Aspect_Post
4412 and then Is_Subprogram
(E
)
4413 and then not Is_Ignored_Ghost_Entity
(E
)
4415 if A_Id
= Aspect_Pre
then
4416 if Is_Ignored
(Aspect
) then
4417 Set_Ignored_Class_Preconditions
(E
,
4418 New_Copy_Tree
(Expr
));
4420 Set_Class_Preconditions
(E
, New_Copy_Tree
(Expr
));
4423 -- Postconditions may split into separate aspects, and we
4424 -- remember the expression before such split (i.e. when
4425 -- the first postcondition is processed).
4427 elsif No
(Class_Postconditions
(E
))
4428 and then No
(Ignored_Class_Postconditions
(E
))
4430 if Is_Ignored
(Aspect
) then
4431 Set_Ignored_Class_Postconditions
(E
,
4432 New_Copy_Tree
(Expr
));
4434 Set_Class_Postconditions
(E
, New_Copy_Tree
(Expr
));
4439 -- If the expressions is of the form A and then B, then
4440 -- we generate separate Pre/Post aspects for the separate
4441 -- clauses. Since we allow multiple pragmas, there is no
4442 -- problem in allowing multiple Pre/Post aspects internally.
4443 -- These should be treated in reverse order (B first and
4444 -- A second) since they are later inserted just after N in
4445 -- the order they are treated. This way, the pragma for A
4446 -- ends up preceding the pragma for B, which may have an
4447 -- importance for the error raised (either constraint error
4448 -- or precondition error).
4450 -- We do not do this for Pre'Class, since we have to put
4451 -- these conditions together in a complex OR expression.
4453 -- We don't do this in GNATprove mode, because it brings no
4454 -- benefit for proof and causes annoyance for flow analysis,
4455 -- which prefers to be as close to the original source code
4456 -- as possible. Also we don't do this when analyzing generic
4457 -- units since it causes spurious visibility errors in the
4458 -- preanalysis of instantiations.
4460 if not GNATprove_Mode
4461 and then (Pname
= Name_Postcondition
4462 or else not Class_Present
(Aspect
))
4463 and then not Inside_A_Generic
4465 while Nkind
(Expr
) = N_And_Then
loop
4466 Insert_After
(Aspect
,
4467 Make_Aspect_Specification
(Sloc
(Left_Opnd
(Expr
)),
4468 Identifier
=> Identifier
(Aspect
),
4469 Expression
=> Relocate_Node
(Left_Opnd
(Expr
)),
4470 Class_Present
=> Class_Present
(Aspect
),
4471 Split_PPC
=> True));
4472 Rewrite
(Expr
, Relocate_Node
(Right_Opnd
(Expr
)));
4473 Eloc
:= Sloc
(Expr
);
4477 -- Build the precondition/postcondition pragma
4479 Aitem
:= Make_Aitem_Pragma
4480 (Pragma_Argument_Associations
=> New_List
(
4481 Make_Pragma_Argument_Association
(Eloc
,
4482 Chars
=> Name_Check
,
4483 Expression
=> Relocate_Expression
(Expr
))),
4484 Pragma_Name
=> Pname
);
4486 -- Add message unless exception messages are suppressed
4488 if not Opt
.Exception_Locations_Suppressed
then
4489 Append_To
(Pragma_Argument_Associations
(Aitem
),
4490 Make_Pragma_Argument_Association
(Eloc
,
4491 Chars
=> Name_Message
,
4493 Make_String_Literal
(Eloc
,
4495 & Get_Name_String
(Pname
)
4497 & Build_Location_String
(Eloc
))));
4500 Set_Is_Delayed_Aspect
(Aspect
);
4502 -- For Pre/Post cases, insert immediately after the entity
4503 -- declaration, since that is the required pragma placement.
4504 -- Note that for these aspects, we do not have to worry
4505 -- about delay issues, since the pragmas themselves deal
4506 -- with delay of visibility for the expression analysis.
4508 Insert_Pragma
(Aitem
);
4515 when Aspect_Test_Case
=> Test_Case
: declare
4517 Comp_Expr
: Node_Id
;
4518 Comp_Assn
: Node_Id
;
4523 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
4524 Error_Msg_Name_1
:= Nam
;
4525 Error_Msg_N
("incorrect placement of aspect %", E
);
4529 if Nkind
(Expr
) /= N_Aggregate
4530 or else Null_Record_Present
(Expr
)
4532 Error_Msg_Name_1
:= Nam
;
4534 ("wrong syntax for aspect % for &", Id
, E
);
4538 -- Check that the expression is a proper aggregate (no
4541 if Paren_Count
(Expr
) /= 0 then
4542 Error_Msg_F
-- CODEFIX
4543 ("redundant parentheses", Expr
);
4547 -- Create the list of arguments for building the Test_Case
4550 Comp_Expr
:= First
(Expressions
(Expr
));
4551 while Present
(Comp_Expr
) loop
4553 Make_Pragma_Argument_Association
(Sloc
(Comp_Expr
),
4554 Expression
=> Relocate_Node
(Comp_Expr
)));
4558 Comp_Assn
:= First
(Component_Associations
(Expr
));
4559 while Present
(Comp_Assn
) loop
4560 if List_Length
(Choices
(Comp_Assn
)) /= 1
4562 Nkind
(First
(Choices
(Comp_Assn
))) /= N_Identifier
4564 Error_Msg_Name_1
:= Nam
;
4566 ("wrong syntax for aspect % for &", Id
, E
);
4571 Make_Pragma_Argument_Association
(Sloc
(Comp_Assn
),
4572 Chars
=> Chars
(First
(Choices
(Comp_Assn
))),
4574 Relocate_Node
(Expression
(Comp_Assn
))));
4578 -- Build the test-case pragma
4580 Aitem
:= Make_Aitem_Pragma
4581 (Pragma_Argument_Associations
=> Args
,
4582 Pragma_Name
=> Name_Test_Case
);
4587 when Aspect_Contract_Cases
=>
4588 Aitem
:= Make_Aitem_Pragma
4589 (Pragma_Argument_Associations
=> New_List
(
4590 Make_Pragma_Argument_Association
(Loc
,
4591 Expression
=> Relocate_Node
(Expr
))),
4592 Pragma_Name
=> Name_Contract_Cases
);
4594 Decorate
(Aspect
, Aitem
);
4595 Insert_Pragma
(Aitem
);
4598 -- Always_Terminates
4600 when Aspect_Always_Terminates
=>
4601 Aitem
:= Make_Aitem_Pragma
4602 (Pragma_Argument_Associations
=> New_List
(
4603 Make_Pragma_Argument_Association
(Loc
,
4604 Expression
=> Relocate_Node
(Expr
))),
4605 Pragma_Name
=> Name_Always_Terminates
);
4607 Decorate
(Aspect
, Aitem
);
4608 Insert_Pragma
(Aitem
);
4611 -- Exceptional_Cases
4613 when Aspect_Exceptional_Cases
=>
4614 Aitem
:= Make_Aitem_Pragma
4615 (Pragma_Argument_Associations
=> New_List
(
4616 Make_Pragma_Argument_Association
(Loc
,
4617 Expression
=> Relocate_Node
(Expr
))),
4618 Pragma_Name
=> Name_Exceptional_Cases
);
4620 Decorate
(Aspect
, Aitem
);
4621 Insert_Pragma
(Aitem
);
4624 -- Subprogram_Variant
4626 when Aspect_Subprogram_Variant
=>
4627 Aitem
:= Make_Aitem_Pragma
4628 (Pragma_Argument_Associations
=> New_List
(
4629 Make_Pragma_Argument_Association
(Loc
,
4630 Expression
=> Relocate_Node
(Expr
))),
4631 Pragma_Name
=> Name_Subprogram_Variant
);
4633 Decorate
(Aspect
, Aitem
);
4634 Insert_Pragma
(Aitem
);
4637 -- Case 5: Special handling for aspects with an optional
4638 -- boolean argument.
4640 -- In the delayed case, the corresponding pragma cannot be
4641 -- generated yet because the evaluation of the boolean needs
4642 -- to be delayed till the freeze point.
4644 when Boolean_Aspects
4645 | Library_Unit_Aspects
4647 Set_Is_Boolean_Aspect
(Aspect
);
4649 -- Lock_Free aspect only apply to protected objects
4651 if A_Id
= Aspect_Lock_Free
then
4652 if Ekind
(E
) /= E_Protected_Type
then
4653 Error_Msg_Name_1
:= Nam
;
4655 ("aspect % only applies to a protected type " &
4660 -- Set the Uses_Lock_Free flag to True if there is no
4661 -- expression or if the expression is True. The
4662 -- evaluation of this aspect should be delayed to the
4663 -- freeze point if we wanted to handle the corner case
4664 -- of "true" or "false" being redefined.
4667 or else Is_True
(Static_Boolean
(Expr
))
4669 Set_Uses_Lock_Free
(E
);
4672 Record_Rep_Item
(E
, Aspect
);
4677 elsif A_Id
in Aspect_Export | Aspect_Import
then
4678 Analyze_Aspect_Export_Import
;
4680 -- Disable_Controlled
4682 elsif A_Id
= Aspect_Disable_Controlled
then
4683 Analyze_Aspect_Disable_Controlled
;
4686 -- Ada 2022 (AI12-0129): Exclusive_Functions
4688 elsif A_Id
= Aspect_Exclusive_Functions
then
4689 if Ekind
(E
) /= E_Protected_Type
then
4690 Error_Msg_Name_1
:= Nam
;
4692 ("aspect % only applies to a protected type " &
4699 -- Ada 2022 (AI12-0363): Full_Access_Only
4701 elsif A_Id
= Aspect_Full_Access_Only
then
4702 Error_Msg_Ada_2022_Feature
("aspect %", Sloc
(Aspect
));
4704 -- Ada 2022 (AI12-0075): static expression functions
4706 elsif A_Id
= Aspect_Static
then
4707 Analyze_Aspect_Static
;
4710 -- Ada 2022 (AI12-0279)
4712 elsif A_Id
= Aspect_Yield
then
4713 Analyze_Aspect_Yield
;
4717 -- Library unit aspects require special handling in the case
4718 -- of a package declaration, the pragma needs to be inserted
4719 -- in the list of declarations for the associated package.
4720 -- There is no issue of visibility delay for these aspects.
4722 if A_Id
in Library_Unit_Aspects
4724 Nkind
(N
) in N_Package_Declaration
4725 | N_Generic_Package_Declaration
4726 and then Nkind
(Parent
(N
)) /= N_Compilation_Unit
4728 -- Aspect is legal on a local instantiation of a library-
4729 -- level generic unit.
4731 and then not Is_Generic_Instance
(Defining_Entity
(N
))
4734 ("incorrect context for library unit aspect&", Id
);
4738 -- Cases where we do not delay
4740 if not Delay_Required
then
4742 -- Exclude aspects Export and Import because their pragma
4743 -- syntax does not map directly to a Boolean aspect.
4745 if A_Id
not in Aspect_Export | Aspect_Import
then
4746 Aitem
:= Make_Aitem_Pragma
4747 (Pragma_Argument_Associations
=> New_List
(
4748 Make_Pragma_Argument_Association
(Sloc
(Ent
),
4749 Expression
=> Ent
)),
4750 Pragma_Name
=> Nam
);
4753 -- In general cases, the corresponding pragma/attribute
4754 -- definition clause will be inserted later at the freezing
4755 -- point, and we do not need to build it now.
4763 -- This is special because for access types we need to generate
4764 -- an attribute definition clause. This also works for single
4765 -- task declarations, but it does not work for task type
4766 -- declarations, because we have the case where the expression
4767 -- references a discriminant of the task type. That can't use
4768 -- an attribute definition clause because we would not have
4769 -- visibility on the discriminant. For that case we must
4770 -- generate a pragma in the task definition.
4772 when Aspect_Storage_Size
=>
4776 if Ekind
(E
) = E_Task_Type
then
4778 Decl
: constant Node_Id
:= Declaration_Node
(E
);
4781 pragma Assert
(Nkind
(Decl
) = N_Task_Type_Declaration
);
4783 -- If no task definition, create one
4785 if No
(Task_Definition
(Decl
)) then
4786 Set_Task_Definition
(Decl
,
4787 Make_Task_Definition
(Loc
,
4788 Visible_Declarations
=> Empty_List
,
4789 End_Label
=> Empty
));
4792 -- Create a pragma and put it at the start of the task
4793 -- definition for the task type declaration.
4795 Aitem
:= Make_Aitem_Pragma
4796 (Pragma_Argument_Associations
=> New_List
(
4797 Make_Pragma_Argument_Association
(Loc
,
4798 Expression
=> Relocate_Node
(Expr
))),
4799 Pragma_Name
=> Name_Storage_Size
);
4803 Visible_Declarations
(Task_Definition
(Decl
)));
4807 -- All other cases, generate attribute definition
4811 Make_Attribute_Definition_Clause
(Loc
,
4813 Chars
=> Name_Storage_Size
,
4814 Expression
=> Relocate_Node
(Expr
));
4818 -- Attach the corresponding pragma/attribute definition clause to
4819 -- the aspect specification node.
4821 if Present
(Aitem
) then
4822 Set_From_Aspect_Specification
(Aitem
);
4825 -- For an aspect that applies to a type, indicate whether it
4826 -- appears on a partial view of the type.
4828 if Is_Type
(E
) and then Is_Private_Type
(E
) then
4829 Set_Aspect_On_Partial_View
(Aspect
);
4832 -- In the context of a compilation unit, we directly put the
4833 -- pragma in the Pragmas_After list of the N_Compilation_Unit_Aux
4834 -- node (no delay is required here) except for aspects on a
4835 -- subprogram body (see below) and a generic package, for which we
4836 -- need to introduce the pragma before building the generic copy
4837 -- (see sem_ch12), and for package instantiations, where the
4838 -- library unit pragmas are better handled early.
4840 if Nkind
(Parent
(N
)) = N_Compilation_Unit
4841 and then (Present
(Aitem
) or else Is_Boolean_Aspect
(Aspect
))
4844 Aux
: constant Node_Id
:= Aux_Decls_Node
(Parent
(N
));
4847 pragma Assert
(Nkind
(Aux
) = N_Compilation_Unit_Aux
);
4849 -- For a Boolean aspect, create the corresponding pragma if
4850 -- no expression or if the value is True.
4852 if Is_Boolean_Aspect
(Aspect
) and then No
(Aitem
) then
4853 if Is_True
(Static_Boolean
(Expr
)) then
4854 Aitem
:= Make_Aitem_Pragma
4855 (Pragma_Argument_Associations
=> New_List
(
4856 Make_Pragma_Argument_Association
(Sloc
(Ent
),
4857 Expression
=> Ent
)),
4858 Pragma_Name
=> Nam
);
4860 Set_From_Aspect_Specification
(Aitem
, True);
4861 Set_Corresponding_Aspect
(Aitem
, Aspect
);
4868 -- If the aspect is on a subprogram body (relevant aspect
4869 -- is Inline), add the pragma in front of the declarations.
4871 if Nkind
(N
) = N_Subprogram_Body
then
4872 if No
(Declarations
(N
)) then
4873 Set_Declarations
(N
, New_List
);
4876 Prepend
(Aitem
, Declarations
(N
));
4878 elsif Nkind
(N
) = N_Generic_Package_Declaration
then
4879 if No
(Visible_Declarations
(Specification
(N
))) then
4880 Set_Visible_Declarations
(Specification
(N
), New_List
);
4884 Visible_Declarations
(Specification
(N
)));
4886 elsif Nkind
(N
) = N_Package_Instantiation
then
4888 Spec
: constant Node_Id
:=
4889 Specification
(Instance_Spec
(N
));
4891 if No
(Visible_Declarations
(Spec
)) then
4892 Set_Visible_Declarations
(Spec
, New_List
);
4895 Prepend
(Aitem
, Visible_Declarations
(Spec
));
4899 if No
(Pragmas_After
(Aux
)) then
4900 Set_Pragmas_After
(Aux
, New_List
);
4903 Append
(Aitem
, Pragmas_After
(Aux
));
4910 -- The evaluation of the aspect is delayed to the freezing point.
4911 -- The pragma or attribute clause if there is one is then attached
4912 -- to the aspect specification which is put in the rep item list.
4914 if Delay_Required
then
4915 if Present
(Aitem
) then
4916 Set_Is_Delayed_Aspect
(Aitem
);
4917 Set_Aspect_Rep_Item
(Aspect
, Aitem
);
4918 Set_Parent
(Aitem
, Aspect
);
4921 Set_Is_Delayed_Aspect
(Aspect
);
4923 -- In the case of Default_Value, link the aspect to base type
4924 -- as well, even though it appears on a first subtype. This is
4925 -- mandated by the semantics of the aspect. Do not establish
4926 -- the link when processing the base type itself as this leads
4927 -- to a rep item circularity.
4929 if A_Id
= Aspect_Default_Value
and then Base_Type
(E
) /= E
then
4930 Set_Has_Delayed_Aspects
(Base_Type
(E
));
4931 Record_Rep_Item
(Base_Type
(E
), Aspect
);
4934 Set_Has_Delayed_Aspects
(E
);
4935 Record_Rep_Item
(E
, Aspect
);
4937 -- When delay is not required and the context is a package or a
4938 -- subprogram body, insert the pragma in the body declarations.
4940 elsif Nkind
(N
) in N_Package_Body | N_Subprogram_Body
then
4941 if No
(Declarations
(N
)) then
4942 Set_Declarations
(N
, New_List
);
4945 -- The pragma is added before source declarations
4947 Prepend_To
(Declarations
(N
), Aitem
);
4949 -- When delay is not required and the context is not a compilation
4950 -- unit, we simply insert the pragma/attribute definition clause
4953 elsif Present
(Aitem
) then
4954 Insert_After
(Ins_Node
, Aitem
);
4960 -- If a nonoverridable aspect is explicitly specified for a
4961 -- derived type, then check consistency with the parent type.
4963 if A_Id
in Nonoverridable_Aspect_Id
4964 and then Nkind
(N
) = N_Full_Type_Declaration
4965 and then Nkind
(Type_Definition
(N
)) = N_Derived_Type_Definition
4966 and then not In_Instance_Body
4969 Parent_Type
: constant Entity_Id
:= Etype
(E
);
4970 Inherited_Aspect
: constant Node_Id
:=
4971 Find_Aspect
(Parent_Type
, A_Id
);
4973 if Present
(Inherited_Aspect
)
4974 and then not Is_Confirming
4975 (A_Id
, Inherited_Aspect
, Aspect
)
4977 Error_Msg_Name_1
:= Aspect_Names
(A_Id
);
4978 Error_Msg_Sloc
:= Sloc
(Inherited_Aspect
);
4981 ("overriding aspect specification for "
4982 & "nonoverridable aspect % does not confirm "
4983 & "aspect specification inherited from #",
4989 when Aspect_Exit
=> null;
4990 end Analyze_One_Aspect
;
4993 end loop Aspect_Loop
;
4995 if Has_Delayed_Aspects
(E
) then
4996 Ensure_Freeze_Node
(E
);
4998 end Analyze_Aspect_Specifications
;
5000 ------------------------------------------------
5001 -- Analyze_Aspects_On_Subprogram_Body_Or_Stub --
5002 ------------------------------------------------
5004 procedure Analyze_Aspects_On_Subprogram_Body_Or_Stub
(N
: Node_Id
) is
5005 Body_Id
: constant Entity_Id
:= Defining_Entity
(N
);
5007 procedure Diagnose_Misplaced_Aspects
(Spec_Id
: Entity_Id
);
5008 -- Body [stub] N has aspects, but they are not properly placed. Emit an
5009 -- error message depending on the aspects involved. Spec_Id denotes the
5010 -- entity of the corresponding spec.
5012 --------------------------------
5013 -- Diagnose_Misplaced_Aspects --
5014 --------------------------------
5016 procedure Diagnose_Misplaced_Aspects
(Spec_Id
: Entity_Id
) is
5017 procedure Misplaced_Aspect_Error
5020 -- Emit an error message concerning misplaced aspect Asp. Ref_Nam is
5021 -- the name of the refined version of the aspect.
5023 ----------------------------
5024 -- Misplaced_Aspect_Error --
5025 ----------------------------
5027 procedure Misplaced_Aspect_Error
5031 Asp_Nam
: constant Name_Id
:= Chars
(Identifier
(Asp
));
5032 Asp_Id
: constant Aspect_Id
:= Get_Aspect_Id
(Asp_Nam
);
5035 -- The corresponding spec already contains the aspect in question
5036 -- and the one appearing on the body must be the refined form:
5038 -- procedure P with Global ...;
5039 -- procedure P with Global ... is ... end P;
5043 if Has_Aspect
(Spec_Id
, Asp_Id
) then
5044 Error_Msg_Name_1
:= Asp_Nam
;
5046 -- Subunits cannot carry aspects that apply to a subprogram
5049 if Nkind
(Parent
(N
)) = N_Subunit
then
5050 Error_Msg_N
("aspect % cannot apply to a subunit", Asp
);
5052 -- Otherwise suggest the refined form
5055 Error_Msg_Name_2
:= Ref_Nam
;
5056 Error_Msg_N
("aspect % should be %", Asp
);
5059 -- Otherwise the aspect must appear on the spec, not on the body
5062 -- procedure P with Global ... is ... end P;
5066 ("aspect specification must appear on initial declaration",
5069 end Misplaced_Aspect_Error
;
5076 -- Start of processing for Diagnose_Misplaced_Aspects
5079 -- Iterate over the aspect specifications and emit specific errors
5080 -- where applicable.
5082 Asp
:= First
(Aspect_Specifications
(N
));
5083 while Present
(Asp
) loop
5084 Asp_Nam
:= Chars
(Identifier
(Asp
));
5086 -- Do not emit errors on aspects that can appear on a subprogram
5087 -- body. This scenario occurs when the aspect specification list
5088 -- contains both misplaced and properly placed aspects.
5090 if Aspect_On_Body_Or_Stub_OK
(Get_Aspect_Id
(Asp_Nam
)) then
5093 -- Special diagnostics for SPARK aspects
5095 elsif Asp_Nam
= Name_Depends
then
5096 Misplaced_Aspect_Error
(Asp
, Name_Refined_Depends
);
5098 elsif Asp_Nam
= Name_Global
then
5099 Misplaced_Aspect_Error
(Asp
, Name_Refined_Global
);
5101 elsif Asp_Nam
= Name_Post
then
5102 Misplaced_Aspect_Error
(Asp
, Name_Refined_Post
);
5104 -- Otherwise a language-defined aspect is misplaced
5108 ("aspect specification must appear on initial declaration",
5114 end Diagnose_Misplaced_Aspects
;
5118 Spec_Id
: constant Entity_Id
:= Unique_Defining_Entity
(N
);
5120 -- Start of processing for Analyze_Aspects_On_Subprogram_Body_Or_Stub
5123 -- Language-defined aspects cannot be associated with a subprogram body
5124 -- [stub] if the subprogram has a spec. Certain implementation defined
5125 -- aspects are allowed to break this rule (for all applicable cases, see
5126 -- table Aspects.Aspect_On_Body_Or_Stub_OK).
5128 if Spec_Id
/= Body_Id
5129 and then Has_Aspects
(N
)
5130 and then not Aspects_On_Body_Or_Stub_OK
(N
)
5132 Diagnose_Misplaced_Aspects
(Spec_Id
);
5134 Analyze_Aspect_Specifications
(N
, Body_Id
);
5136 end Analyze_Aspects_On_Subprogram_Body_Or_Stub
;
5138 -----------------------
5139 -- Analyze_At_Clause --
5140 -----------------------
5142 -- An at clause is replaced by the corresponding Address attribute
5143 -- definition clause that is the preferred approach in Ada 95.
5145 procedure Analyze_At_Clause
(N
: Node_Id
) is
5146 CS
: constant Boolean := Comes_From_Source
(N
);
5149 -- This is an obsolescent feature
5151 Check_Restriction
(No_Obsolescent_Features
, N
);
5153 if Warn_On_Obsolescent_Feature
then
5155 ("?j?at clause is an obsolescent feature (RM J.7(2))", N
);
5157 ("\?j?use address attribute definition clause instead", N
);
5160 -- Rewrite as address clause
5163 Make_Attribute_Definition_Clause
(Sloc
(N
),
5164 Name
=> Identifier
(N
),
5165 Chars
=> Name_Address
,
5166 Expression
=> Expression
(N
)));
5168 -- We preserve Comes_From_Source, since logically the clause still comes
5169 -- from the source program even though it is changed in form.
5171 Set_Comes_From_Source
(N
, CS
);
5173 -- Analyze rewritten clause
5175 Analyze_Attribute_Definition_Clause
(N
);
5176 end Analyze_At_Clause
;
5178 -----------------------------------------
5179 -- Analyze_Attribute_Definition_Clause --
5180 -----------------------------------------
5182 procedure Analyze_Attribute_Definition_Clause
(N
: Node_Id
) is
5183 Loc
: constant Source_Ptr
:= Sloc
(N
);
5184 Nam
: constant Node_Id
:= Name
(N
);
5185 Attr
: constant Name_Id
:= Chars
(N
);
5186 Expr
: constant Node_Id
:= Expression
(N
);
5187 Id
: constant Attribute_Id
:= Get_Attribute_Id
(Attr
);
5190 -- The entity of Nam after it is analyzed. In the case of an incomplete
5191 -- type, this is the underlying type.
5194 -- The underlying entity to which the attribute applies. Generally this
5195 -- is the Underlying_Type of Ent, except in the case where the clause
5196 -- applies to the full view of an incomplete or private type, in which
5197 -- case U_Ent is just a copy of Ent.
5199 FOnly
: Boolean := False;
5200 -- Reset to True for subtype specific attribute (Alignment, Size)
5201 -- and for stream attributes, i.e. those cases where in the call to
5202 -- Rep_Item_Too_Late, FOnly is set True so that only the freezing rules
5203 -- are checked. Note that the case of stream attributes is not clear
5204 -- from the RM, but see AI95-00137. Also, the RM seems to disallow
5205 -- Storage_Size for derived task types, but that is also clearly
5208 procedure Analyze_Put_Image_TSS_Definition
;
5210 procedure Analyze_Stream_TSS_Definition
(TSS_Nam
: TSS_Name_Type
);
5211 -- Common processing for 'Read, 'Write, 'Input and 'Output attribute
5212 -- definition clauses.
5214 function Duplicate_Clause
return Boolean;
5215 -- This routine checks if the aspect for U_Ent being given by attribute
5216 -- definition clause N is for an aspect that has already been specified,
5217 -- and if so gives an error message. If there is a duplicate, True is
5218 -- returned, otherwise there is no error, and False is returned. Size
5219 -- and Value_Size are considered to conflict, but for compatibility,
5220 -- this is merely a warning.
5222 procedure Check_Indexing_Functions
;
5223 -- Check that the function in Constant_Indexing or Variable_Indexing
5224 -- attribute has the proper type structure. If the name is overloaded,
5225 -- check that some interpretation is legal.
5227 procedure Check_Iterator_Functions
;
5228 -- Check that there is a single function in Default_Iterator attribute
5229 -- that has the proper type structure.
5231 function Check_Primitive_Function
(Subp
: Entity_Id
) return Boolean;
5232 -- Common legality check for the previous two
5234 -----------------------------------
5235 -- Analyze_Put_Image_TSS_Definition --
5236 -----------------------------------
5238 procedure Analyze_Put_Image_TSS_Definition
is
5239 Subp
: Entity_Id
:= Empty
;
5244 function Has_Good_Profile
5246 Report
: Boolean := False) return Boolean;
5247 -- Return true if the entity is a subprogram with an appropriate
5248 -- profile for the attribute being defined. If result is False and
5249 -- Report is True, function emits appropriate error.
5251 ----------------------
5252 -- Has_Good_Profile --
5253 ----------------------
5255 function Has_Good_Profile
5257 Report
: Boolean := False) return Boolean
5263 if Ekind
(Subp
) /= E_Procedure
then
5267 F
:= First_Formal
(Subp
);
5273 if Base_Type
(Etype
(F
))
5274 /= Class_Wide_Type
(RTE
(RE_Root_Buffer_Type
))
5278 ("wrong type for Put_Image procedure''s first parameter",
5279 Parameter_Type
(Parent
(F
)));
5285 if Parameter_Mode
(F
) /= E_In_Out_Parameter
then
5288 ("wrong mode for Put_Image procedure''s first parameter",
5299 -- Verify that the prefix of the attribute and the local name for
5300 -- the type of the formal match.
5302 if Base_Type
(Typ
) /= Base_Type
(Ent
) then
5305 ("wrong type for Put_Image procedure''s second parameter",
5306 Parameter_Type
(Parent
(F
)));
5312 if Parameter_Mode
(F
) /= E_In_Parameter
then
5315 ("wrong mode for Put_Image procedure''s second parameter",
5322 if Present
(Next_Formal
(F
)) then
5327 end Has_Good_Profile
;
5329 -- Start of processing for Analyze_Put_Image_TSS_Definition
5332 if not Is_Type
(U_Ent
) then
5333 Error_Msg_N
("local name must be a subtype", Nam
);
5336 elsif not Is_First_Subtype
(U_Ent
) then
5337 Error_Msg_N
("local name must be a first subtype", Nam
);
5341 Pnam
:= TSS
(Base_Type
(U_Ent
), TSS_Put_Image
);
5343 -- If Pnam is present, it can be either inherited from an ancestor
5344 -- type (in which case it is legal to redefine it for this type), or
5345 -- be a previous definition of the attribute for the same type (in
5346 -- which case it is illegal).
5348 -- In the first case, it will have been analyzed already, and we can
5349 -- check that its profile does not match the expected profile for the
5350 -- Put_Image attribute of U_Ent. In the second case, either Pnam has
5351 -- been analyzed (and has the expected profile), or it has not been
5352 -- analyzed yet (case of a type that has not been frozen yet and for
5353 -- which Put_Image has been set using Set_TSS).
5356 and then (No
(First_Entity
(Pnam
)) or else Has_Good_Profile
(Pnam
))
5358 Error_Msg_Sloc
:= Sloc
(Pnam
);
5359 Error_Msg_Name_1
:= Attr
;
5360 Error_Msg_N
("% attribute already defined #", Nam
);
5366 if Is_Entity_Name
(Expr
) then
5367 if not Is_Overloaded
(Expr
) then
5368 if Has_Good_Profile
(Entity
(Expr
), Report
=> True) then
5369 Subp
:= Entity
(Expr
);
5373 Get_First_Interp
(Expr
, I
, It
);
5374 while Present
(It
.Nam
) loop
5375 if Has_Good_Profile
(It
.Nam
) then
5380 Get_Next_Interp
(I
, It
);
5385 if Present
(Subp
) then
5386 if Is_Abstract_Subprogram
(Subp
) then
5387 Error_Msg_N
("Put_Image subprogram must not be abstract", Expr
);
5391 Set_Entity
(Expr
, Subp
);
5392 Set_Etype
(Expr
, Etype
(Subp
));
5394 New_Put_Image_Subprogram
(N
, U_Ent
, Subp
);
5397 Error_Msg_Name_1
:= Attr
;
5398 Error_Msg_N
("incorrect expression for% attribute", Expr
);
5400 end Analyze_Put_Image_TSS_Definition
;
5402 -----------------------------------
5403 -- Analyze_Stream_TSS_Definition --
5404 -----------------------------------
5406 procedure Analyze_Stream_TSS_Definition
(TSS_Nam
: TSS_Name_Type
) is
5407 Subp
: Entity_Id
:= Empty
;
5412 Is_Read
: constant Boolean := (TSS_Nam
= TSS_Stream_Read
);
5413 -- True for Read attribute, False for other attributes
5415 function Has_Good_Profile
5417 Report
: Boolean := False) return Boolean;
5418 -- Return true if the entity is a subprogram with an appropriate
5419 -- profile for the attribute being defined. If result is False and
5420 -- Report is True, function emits appropriate error.
5422 ----------------------
5423 -- Has_Good_Profile --
5424 ----------------------
5426 function Has_Good_Profile
5428 Report
: Boolean := False) return Boolean
5430 Expected_Ekind
: constant array (Boolean) of Entity_Kind
:=
5431 (False => E_Procedure
, True => E_Function
);
5432 Is_Function
: constant Boolean := (TSS_Nam
= TSS_Stream_Input
);
5437 if Ekind
(Subp
) /= Expected_Ekind
(Is_Function
) then
5441 F
:= First_Formal
(Subp
);
5444 or else Ekind
(Etype
(F
)) /= E_Anonymous_Access_Type
5445 or else Base_Type
(Designated_Type
(Etype
(F
))) /=
5446 Class_Wide_Type
(RTE
(RE_Root_Stream_Type
))
5451 if not Is_Function
then
5455 Expected_Mode
: constant array (Boolean) of Entity_Kind
:=
5456 (False => E_In_Parameter
,
5457 True => E_Out_Parameter
);
5459 if Parameter_Mode
(F
) /= Expected_Mode
(Is_Read
) then
5467 Typ
:= Etype
(Subp
);
5470 -- Verify that the prefix of the attribute and the local name for
5471 -- the type of the formal match.
5473 if Base_Type
(Typ
) /= Base_Type
(Ent
) then
5477 if Present
(Next_Formal
(F
)) then
5480 elsif not Is_Scalar_Type
(Typ
)
5481 and then not Is_First_Subtype
(Typ
)
5482 and then not Is_Class_Wide_Type
(Typ
)
5484 if Report
and not Is_First_Subtype
(Typ
) then
5486 ("subtype of formal in stream operation must be a first "
5487 & "subtype", Parameter_Type
(Parent
(F
)));
5495 end Has_Good_Profile
;
5497 -- Start of processing for Analyze_Stream_TSS_Definition
5502 if not Is_Type
(U_Ent
) then
5503 Error_Msg_N
("local name must be a subtype", Nam
);
5506 elsif not Is_First_Subtype
(U_Ent
) then
5507 Error_Msg_N
("local name must be a first subtype", Nam
);
5511 Pnam
:= TSS
(Base_Type
(U_Ent
), TSS_Nam
);
5513 -- If Pnam is present, it can be either inherited from an ancestor
5514 -- type (in which case it is legal to redefine it for this type), or
5515 -- be a previous definition of the attribute for the same type (in
5516 -- which case it is illegal).
5518 -- In the first case, it will have been analyzed already, and we
5519 -- can check that its profile does not match the expected profile
5520 -- for a stream attribute of U_Ent. In the second case, either Pnam
5521 -- has been analyzed (and has the expected profile), or it has not
5522 -- been analyzed yet (case of a type that has not been frozen yet
5523 -- and for which the stream attribute has been set using Set_TSS).
5526 and then (No
(First_Entity
(Pnam
)) or else Has_Good_Profile
(Pnam
))
5528 Error_Msg_Sloc
:= Sloc
(Pnam
);
5529 Error_Msg_Name_1
:= Attr
;
5530 Error_Msg_N
("% attribute already defined #", Nam
);
5536 if Is_Entity_Name
(Expr
) then
5537 if not Is_Overloaded
(Expr
) then
5538 if Has_Good_Profile
(Entity
(Expr
), Report
=> True) then
5539 Subp
:= Entity
(Expr
);
5543 Get_First_Interp
(Expr
, I
, It
);
5544 while Present
(It
.Nam
) loop
5545 if Has_Good_Profile
(It
.Nam
) then
5550 Get_Next_Interp
(I
, It
);
5555 if Present
(Subp
) then
5556 if Is_Abstract_Subprogram
(Subp
) then
5557 Error_Msg_N
("stream subprogram must not be abstract", Expr
);
5560 -- A stream subprogram for an interface type must be a null
5561 -- procedure (RM 13.13.2 (38/3)). Note that the class-wide type
5562 -- of an interface is not an interface type (3.9.4 (6.b/2)).
5564 elsif Is_Interface
(U_Ent
)
5565 and then not Is_Class_Wide_Type
(U_Ent
)
5566 and then not Inside_A_Generic
5568 (Ekind
(Subp
) = E_Function
5572 (Unit_Declaration_Node
(Ultimate_Alias
(Subp
)))))
5575 ("stream subprogram for interface type must be null "
5576 & "procedure", Expr
);
5579 Set_Entity
(Expr
, Subp
);
5580 Set_Etype
(Expr
, Etype
(Subp
));
5582 New_Stream_Subprogram
(N
, U_Ent
, Subp
, TSS_Nam
);
5585 Error_Msg_Name_1
:= Attr
;
5587 if Is_Class_Wide_Type
(Base_Type
(Ent
)) then
5589 ("incorrect expression for class-wide% attribute", Expr
);
5591 Error_Msg_N
("incorrect expression for% attribute", Expr
);
5594 end Analyze_Stream_TSS_Definition
;
5596 ------------------------------
5597 -- Check_Indexing_Functions --
5598 ------------------------------
5600 procedure Check_Indexing_Functions
is
5601 Indexing_Found
: Boolean := False;
5603 procedure Check_Inherited_Indexing
;
5604 -- For a derived type, check that for a derived type, a specification
5605 -- of an indexing aspect can only be confirming, i.e. uses the same
5606 -- name as in the parent type.
5607 -- AI12-0160: Verify that an indexing cannot be specified for
5608 -- a derived type unless it is specified for the parent.
5610 procedure Check_One_Function
(Subp
: Entity_Id
);
5611 -- Check one possible interpretation. Sets Indexing_Found True if a
5612 -- legal indexing function is found.
5614 procedure Illegal_Indexing
(Msg
: String);
5615 -- Diagnose illegal indexing function if not overloaded. In the
5616 -- overloaded case indicate that no legal interpretation exists.
5618 ------------------------------
5619 -- Check_Inherited_Indexing --
5620 ------------------------------
5622 procedure Check_Inherited_Indexing
is
5623 Inherited
: Node_Id
;
5624 Other_Indexing
: Node_Id
;
5627 if Attr
= Name_Constant_Indexing
then
5629 Find_Aspect
(Etype
(Ent
), Aspect_Constant_Indexing
);
5631 Find_Aspect
(Etype
(Ent
), Aspect_Variable_Indexing
);
5633 else pragma Assert
(Attr
= Name_Variable_Indexing
);
5635 Find_Aspect
(Etype
(Ent
), Aspect_Variable_Indexing
);
5637 Find_Aspect
(Etype
(Ent
), Aspect_Constant_Indexing
);
5640 if Present
(Inherited
) then
5641 if Debug_Flag_Dot_XX
then
5644 -- OK if current attribute_definition_clause is expansion of
5645 -- inherited aspect.
5647 elsif Aspect_Rep_Item
(Inherited
) = N
then
5650 -- Check if this is a confirming specification. The name
5651 -- may be overloaded between the parent operation and the
5652 -- inherited one, so we check that the Chars fields match.
5654 elsif Is_Entity_Name
(Expression
(Inherited
))
5655 and then Chars
(Entity
(Expression
(Inherited
))) =
5656 Chars
(Entity
(Expression
(N
)))
5658 Indexing_Found
:= True;
5660 -- Indicate the operation that must be overridden, rather than
5661 -- redefining the indexing aspect.
5665 ("indexing function already inherited from parent type");
5667 ("!override & instead",
5668 N
, Entity
(Expression
(Inherited
)));
5671 -- If not inherited and the parent has another indexing function
5672 -- this is illegal, because it leads to inconsistent results in
5673 -- class-wide calls.
5675 elsif Present
(Other_Indexing
) then
5677 ("cannot specify indexing operation on derived type"
5678 & " if not specified for parent", N
);
5680 end Check_Inherited_Indexing
;
5682 ------------------------
5683 -- Check_One_Function --
5684 ------------------------
5686 procedure Check_One_Function
(Subp
: Entity_Id
) is
5687 Default_Element
: Node_Id
;
5688 Ret_Type
: constant Entity_Id
:= Etype
(Subp
);
5691 if not Is_Overloadable
(Subp
) then
5692 Illegal_Indexing
("illegal indexing function for type&");
5695 elsif Scope
(Subp
) /= Scope
(Ent
) then
5696 if Nkind
(Expr
) = N_Expanded_Name
then
5698 -- Indexing function can't be declared elsewhere
5701 ("indexing function must be declared"
5702 & " in scope of type&");
5705 if Is_Derived_Type
(Ent
) then
5706 Check_Inherited_Indexing
;
5711 elsif No
(First_Formal
(Subp
)) then
5713 ("Indexing requires a function that applies to type&");
5716 elsif No
(Next_Formal
(First_Formal
(Subp
))) then
5718 ("indexing function must have at least two parameters");
5721 elsif Is_Derived_Type
(Ent
) then
5722 Check_Inherited_Indexing
;
5725 if not Check_Primitive_Function
(Subp
) then
5727 ("Indexing aspect requires a function that applies to type&");
5731 -- If partial declaration exists, verify that it is not tagged.
5733 if Ekind
(Current_Scope
) = E_Package
5734 and then Has_Private_Declaration
(Ent
)
5735 and then From_Aspect_Specification
(N
)
5737 List_Containing
(Parent
(Ent
)) =
5738 Private_Declarations
5739 (Specification
(Unit_Declaration_Node
(Current_Scope
)))
5740 and then Nkind
(N
) = N_Attribute_Definition_Clause
5747 First
(Visible_Declarations
5749 (Unit_Declaration_Node
(Current_Scope
))));
5751 while Present
(Decl
) loop
5752 if Nkind
(Decl
) = N_Private_Type_Declaration
5753 and then Ent
= Full_View
(Defining_Identifier
(Decl
))
5754 and then Tagged_Present
(Decl
)
5755 and then No
(Aspect_Specifications
(Decl
))
5758 ("Indexing aspect cannot be specified on full view "
5759 & "if partial view is tagged");
5768 -- An indexing function must return either the default element of
5769 -- the container, or a reference type. For variable indexing it
5770 -- must be the latter.
5773 Find_Value_Of_Aspect
5774 (Etype
(First_Formal
(Subp
)), Aspect_Iterator_Element
);
5776 if Present
(Default_Element
) then
5777 Analyze
(Default_Element
);
5780 -- For variable_indexing the return type must be a reference type
5782 if Attr
= Name_Variable_Indexing
then
5783 if not Has_Implicit_Dereference
(Ret_Type
) then
5785 ("variable indexing must return a reference type");
5788 elsif Is_Access_Constant
5789 (Etype
(First_Discriminant
(Ret_Type
)))
5792 ("variable indexing must return an access to variable");
5797 if Has_Implicit_Dereference
(Ret_Type
)
5800 (Etype
(Get_Reference_Discriminant
(Ret_Type
)))
5803 ("constant indexing must return an access to constant");
5806 elsif Is_Access_Type
(Etype
(First_Formal
(Subp
)))
5807 and then not Is_Access_Constant
(Etype
(First_Formal
(Subp
)))
5810 ("constant indexing must apply to an access to constant");
5815 -- All checks succeeded
5817 Indexing_Found
:= True;
5818 end Check_One_Function
;
5820 -----------------------
5821 -- Illegal_Indexing --
5822 -----------------------
5824 procedure Illegal_Indexing
(Msg
: String) is
5826 Error_Msg_NE
(Msg
, N
, Ent
);
5827 end Illegal_Indexing
;
5829 -- Start of processing for Check_Indexing_Functions
5833 Check_Inherited_Indexing
;
5838 if not Is_Overloaded
(Expr
) then
5839 Check_One_Function
(Entity
(Expr
));
5847 Indexing_Found
:= False;
5848 Get_First_Interp
(Expr
, I
, It
);
5849 while Present
(It
.Nam
) loop
5851 -- Note that analysis will have added the interpretation
5852 -- that corresponds to the dereference. We only check the
5853 -- subprogram itself. Ignore homonyms that may come from
5854 -- derived types in the context.
5856 if Is_Overloadable
(It
.Nam
)
5857 and then Comes_From_Source
(It
.Nam
)
5859 Check_One_Function
(It
.Nam
);
5862 Get_Next_Interp
(I
, It
);
5867 if not Indexing_Found
and then not Error_Posted
(N
) then
5869 ("aspect Indexing requires a local function that applies to "
5870 & "type&", Expr
, Ent
);
5872 end Check_Indexing_Functions
;
5874 ------------------------------
5875 -- Check_Iterator_Functions --
5876 ------------------------------
5878 procedure Check_Iterator_Functions
is
5879 function Valid_Default_Iterator
(Subp
: Entity_Id
;
5880 Ref_Node
: Node_Id
:= Empty
)
5882 -- Check one possible interpretation for validity. If
5883 -- Ref_Node is present report errors on violations.
5885 ----------------------------
5886 -- Valid_Default_Iterator --
5887 ----------------------------
5889 function Valid_Default_Iterator
(Subp
: Entity_Id
;
5890 Ref_Node
: Node_Id
:= Empty
)
5893 Return_Type
: constant Entity_Id
:= Etype
(Etype
(Subp
));
5894 Return_Node
: Node_Id
;
5895 Root_T
: constant Entity_Id
:= Root_Type
(Return_Type
);
5898 function Valid_Iterator_Name
(E
: Entity_Id
) return Boolean
5899 is (Chars
(E
) in Name_Forward_Iterator | Name_Reversible_Iterator
);
5901 function Valid_Iterator_Name
(L
: Elist_Id
) return Boolean;
5903 -------------------------
5904 -- Valid_Iterator_Name --
5905 -------------------------
5907 function Valid_Iterator_Name
(L
: Elist_Id
) return Boolean
5909 Iface_Elmt
: Elmt_Id
:= First_Elmt
(L
);
5911 while Present
(Iface_Elmt
) loop
5912 if Valid_Iterator_Name
(Node
(Iface_Elmt
)) then
5915 Next_Elmt
(Iface_Elmt
);
5919 end Valid_Iterator_Name
;
5922 if Subp
= Any_Id
then
5923 if Present
(Ref_Node
) then
5925 -- Subp is not resolved and an error will be posted about
5928 Error_Msg_N
("improper function for default iterator!",
5935 if not Check_Primitive_Function
(Subp
) then
5936 if Present
(Ref_Node
) then
5937 Error_Msg_N
("improper function for default iterator!",
5939 Error_Msg_Sloc
:= Sloc
(Subp
);
5941 ("\\default iterator defined # "
5942 & "must be a primitive function",
5949 -- The return type must be derived from a type in an instance
5950 -- of Iterator.Interfaces, and thus its root type must have a
5953 if not Valid_Iterator_Name
(Root_T
)
5954 and then not (Has_Interfaces
(Return_Type
) and then
5955 Valid_Iterator_Name
(Interfaces
(Return_Type
)))
5957 if Present
(Ref_Node
) then
5959 Return_Node
:= Result_Definition
(Parent
(Subp
));
5961 Error_Msg_N
("improper function for default iterator!",
5963 Error_Msg_Sloc
:= Sloc
(Return_Node
);
5964 Error_Msg_NE
("\\return type & # "
5965 & "must inherit from either "
5966 & "Forward_Iterator or Reversible_Iterator",
5967 Ref_Node
, Return_Node
);
5973 Formal
:= First_Formal
(Subp
);
5975 -- False if any subsequent formal has no default expression
5977 Next_Formal
(Formal
);
5978 while Present
(Formal
) loop
5979 if No
(Expression
(Parent
(Formal
))) then
5980 if Present
(Ref_Node
) then
5981 Error_Msg_N
("improper function for default iterator!",
5983 Error_Msg_Sloc
:= Sloc
(Formal
);
5984 Error_Msg_NE
("\\formal parameter & # "
5985 & "must have a default expression",
5992 Next_Formal
(Formal
);
5995 -- True if all subsequent formals have default expressions
5998 end Valid_Default_Iterator
;
6002 -- Start of processing for Check_Iterator_Functions
6007 if not Is_Entity_Name
(Expr
) then
6008 Error_Msg_N
("aspect Iterator must be a function name", Expr
);
6011 if not Is_Overloaded
(Expr
) then
6012 if Entity
(Expr
) /= Any_Id
6013 and then not Check_Primitive_Function
(Entity
(Expr
))
6016 ("aspect Indexing requires a function that applies to type&",
6017 Entity
(Expr
), Ent
);
6020 -- Flag the default_iterator as well as the denoted function.
6022 Ignore
:= Valid_Default_Iterator
(Entity
(Expr
), Expr
);
6026 Default
: Entity_Id
:= Empty
;
6031 Get_First_Interp
(Expr
, I
, It
);
6032 while Present
(It
.Nam
) loop
6033 if not Check_Primitive_Function
(It
.Nam
)
6034 or else not Valid_Default_Iterator
(It
.Nam
)
6038 elsif Present
(Default
) then
6040 -- An explicit one should override an implicit one
6042 if Comes_From_Source
(Default
) =
6043 Comes_From_Source
(It
.Nam
)
6045 Error_Msg_N
("default iterator must be unique", Expr
);
6046 Error_Msg_Sloc
:= Sloc
(Default
);
6047 Error_Msg_N
("\\possible interpretation#", Expr
);
6048 Error_Msg_Sloc
:= Sloc
(It
.Nam
);
6049 Error_Msg_N
("\\possible interpretation#", Expr
);
6051 elsif Comes_From_Source
(It
.Nam
) then
6058 Get_Next_Interp
(I
, It
);
6061 if Present
(Default
) then
6062 Set_Entity
(Expr
, Default
);
6063 Set_Is_Overloaded
(Expr
, False);
6066 ("no interpretation is a valid default iterator!", Expr
);
6070 end Check_Iterator_Functions
;
6072 -------------------------------
6073 -- Check_Primitive_Function --
6074 -------------------------------
6076 function Check_Primitive_Function
(Subp
: Entity_Id
) return Boolean is
6080 if Ekind
(Subp
) /= E_Function
then
6084 if No
(First_Formal
(Subp
)) then
6087 Ctrl
:= Etype
(First_Formal
(Subp
));
6090 -- To be a primitive operation subprogram has to be in same scope.
6092 if Scope
(Ctrl
) /= Scope
(Subp
) then
6096 -- Type of formal may be the class-wide type, an access to such,
6097 -- or an incomplete view.
6100 or else Ctrl
= Class_Wide_Type
(Ent
)
6102 (Ekind
(Ctrl
) = E_Anonymous_Access_Type
6103 and then (Designated_Type
(Ctrl
) = Ent
6105 Designated_Type
(Ctrl
) = Class_Wide_Type
(Ent
)))
6107 (Ekind
(Ctrl
) = E_Incomplete_Type
6108 and then Full_View
(Ctrl
) = Ent
)
6116 end Check_Primitive_Function
;
6118 ----------------------
6119 -- Duplicate_Clause --
6120 ----------------------
6122 function Duplicate_Clause
return Boolean is
6124 function Check_One_Attr
(Attr_1
, Attr_2
: Name_Id
) return Boolean;
6125 -- Check for one attribute; Attr_1 is the attribute_designator we are
6126 -- looking for. Attr_2 is the attribute_designator of the current
6127 -- node. Normally, this is called just once by Duplicate_Clause, with
6128 -- Attr_1 = Attr_2. However, it needs to be called twice for Size and
6129 -- Value_Size, because these mean the same thing. For compatibility,
6130 -- we allow specifying both Size and Value_Size, but only if the two
6133 --------------------
6134 -- Check_One_Attr --
6135 --------------------
6137 function Check_One_Attr
(Attr_1
, Attr_2
: Name_Id
) return Boolean is
6138 A
: constant Node_Id
:=
6139 Get_Rep_Item
(U_Ent
, Attr_1
, Check_Parents
=> False);
6142 if Attr_1
= Attr_2
then
6143 Error_Msg_Name_1
:= Attr_1
;
6144 Error_Msg_Sloc
:= Sloc
(A
);
6145 Error_Msg_NE
("aspect% for & previously given#", N
, U_Ent
);
6148 pragma Assert
(Attr_1
in Name_Size | Name_Value_Size
);
6149 pragma Assert
(Attr_2
in Name_Size | Name_Value_Size
);
6151 Error_Msg_Name_1
:= Attr_2
;
6152 Error_Msg_Name_2
:= Attr_1
;
6153 Error_Msg_Sloc
:= Sloc
(A
);
6154 Error_Msg_NE
("?% for & conflicts with % #", N
, U_Ent
);
6163 -- Start of processing for Duplicate_Clause
6166 -- Nothing to do if this attribute definition clause comes from
6167 -- an aspect specification, since we could not be duplicating an
6168 -- explicit clause, and we dealt with the case of duplicated aspects
6169 -- in Analyze_Aspect_Specifications.
6171 if From_Aspect_Specification
(N
) then
6175 -- Special cases for Size and Value_Size
6177 if (Chars
(N
) = Name_Size
6178 and then Check_One_Attr
(Name_Value_Size
, Name_Size
))
6180 (Chars
(N
) = Name_Value_Size
6181 and then Check_One_Attr
(Name_Size
, Name_Value_Size
))
6186 -- Normal case (including Size and Value_Size)
6188 return Check_One_Attr
(Chars
(N
), Chars
(N
));
6189 end Duplicate_Clause
;
6191 -- Start of processing for Analyze_Attribute_Definition_Clause
6194 -- The following code is a defense against recursion. Not clear that
6195 -- this can happen legitimately, but perhaps some error situations can
6196 -- cause it, and we did see this recursion during testing.
6198 if Analyzed
(N
) then
6201 Set_Analyzed
(N
, True);
6204 Check_Restriction_No_Use_Of_Attribute
(N
);
6206 if Is_Aspect_Id
(Chars
(N
)) then
6207 -- 6.1/3 No_Specification_of_Aspect: Identifies an aspect for which
6208 -- no aspect_specification, attribute_definition_clause, or pragma
6210 Check_Restriction_No_Specification_Of_Aspect
(N
);
6213 -- Ignore some selected attributes in CodePeer mode since they are not
6214 -- relevant in this context.
6216 if CodePeer_Mode
then
6219 -- Ignore Component_Size in CodePeer mode, to avoid changing the
6220 -- internal representation of types by implicitly packing them.
6222 when Attribute_Component_Size
=>
6223 Rewrite
(N
, Make_Null_Statement
(Sloc
(N
)));
6231 -- Process Ignore_Rep_Clauses option
6233 if Ignore_Rep_Clauses
then
6236 -- The following should be ignored. They do not affect legality
6237 -- and may be target dependent. The basic idea of -gnatI is to
6238 -- ignore any rep clauses that may be target dependent but do not
6239 -- affect legality (except possibly to be rejected because they
6240 -- are incompatible with the compilation target).
6242 when Attribute_Alignment
6243 | Attribute_Bit_Order
6244 | Attribute_Component_Size
6245 | Attribute_Default_Scalar_Storage_Order
6246 | Attribute_Machine_Radix
6247 | Attribute_Object_Size
6248 | Attribute_Scalar_Storage_Order
6251 | Attribute_Stream_Size
6252 | Attribute_Value_Size
6254 Kill_Rep_Clause
(N
);
6257 -- The following should not be ignored, because in the first place
6258 -- they are reasonably portable, and should not cause problems
6259 -- in compiling code from another target, and also they do affect
6260 -- legality, e.g. failing to provide a stream attribute for a type
6261 -- may make a program illegal.
6263 when Attribute_External_Tag
6266 | Attribute_Put_Image
6268 | Attribute_Simple_Storage_Pool
6269 | Attribute_Storage_Pool
6270 | Attribute_Storage_Size
6275 -- We do not do anything here with address clauses, they will be
6276 -- removed by Freeze later on, but for now, it works better to
6277 -- keep them in the tree.
6279 when Attribute_Address
=>
6282 -- Other cases are errors ("attribute& cannot be set with
6283 -- definition clause"), which will be caught below.
6291 Ent
:= Entity
(Nam
);
6293 if Rep_Item_Too_Early
(Ent
, N
) then
6297 -- Rep clause applies to (underlying) full view of private or incomplete
6298 -- type if we have one (if not, this is a premature use of the type).
6299 -- However, some semantic checks need to be done on the specified entity
6300 -- i.e. the private view, so we save it in Ent.
6302 if Is_Private_Type
(Ent
)
6303 and then Is_Derived_Type
(Ent
)
6304 and then not Is_Tagged_Type
(Ent
)
6305 and then No
(Full_View
(Ent
))
6306 and then No
(Underlying_Full_View
(Ent
))
6310 elsif Ekind
(Ent
) = E_Incomplete_Type
then
6312 -- The attribute applies to the full view, set the entity of the
6313 -- attribute definition accordingly.
6315 Ent
:= Underlying_Type
(Ent
);
6317 Set_Entity
(Nam
, Ent
);
6320 U_Ent
:= Underlying_Type
(Ent
);
6323 -- Avoid cascaded error
6325 if Etype
(Nam
) = Any_Type
then
6328 -- Must be declared in current scope or in case of an aspect
6329 -- specification, must be visible in current scope.
6331 elsif Scope
(Ent
) /= Current_Scope
6333 not (From_Aspect_Specification
(N
)
6334 and then Scope_Within_Or_Same
(Current_Scope
, Scope
(Ent
)))
6336 Error_Msg_N
("entity must be declared in this scope", Nam
);
6339 -- Must not be a source renaming (we do have some cases where the
6340 -- expander generates a renaming, and those cases are OK, in such
6341 -- cases any attribute applies to the renamed object as well).
6343 elsif Is_Object
(Ent
)
6344 and then Present
(Renamed_Object
(Ent
))
6346 -- In the case of a renamed object from source, this is an error
6347 -- unless the object is an aggregate and the renaming is created
6348 -- for an object declaration.
6350 if Comes_From_Source
(Renamed_Object
(Ent
))
6351 and then Nkind
(Renamed_Object
(Ent
)) /= N_Aggregate
6353 Get_Name_String
(Chars
(N
));
6354 Error_Msg_Strlen
:= Name_Len
;
6355 Error_Msg_String
(1 .. Name_Len
) := Name_Buffer
(1 .. Name_Len
);
6357 ("~ clause not allowed for a renaming declaration "
6358 & "(RM 13.1(6))", Nam
);
6361 -- For the case of a compiler generated renaming, the attribute
6362 -- definition clause applies to the renamed object created by the
6363 -- expander. The easiest general way to handle this is to create a
6364 -- copy of the attribute definition clause for this object.
6366 elsif Is_Entity_Name
(Renamed_Object
(Ent
)) then
6368 Make_Attribute_Definition_Clause
(Loc
,
6370 New_Occurrence_Of
(Entity
(Renamed_Object
(Ent
)), Loc
),
6372 Expression
=> Duplicate_Subexpr
(Expression
(N
))));
6374 -- If the renamed object is not an entity, it must be a dereference
6375 -- of an unconstrained function call, and we must introduce a new
6376 -- declaration to capture the expression. This is needed in the case
6377 -- of 'Alignment, where the original declaration must be rewritten.
6381 (Nkind
(Renamed_Object
(Ent
)) = N_Explicit_Dereference
);
6385 -- If no underlying entity, use entity itself, applies to some
6386 -- previously detected error cases ???
6388 elsif No
(U_Ent
) then
6391 -- Cannot specify for a subtype (exception Object/Value_Size)
6393 elsif Is_Type
(U_Ent
)
6394 and then not Is_First_Subtype
(U_Ent
)
6395 and then Id
/= Attribute_Object_Size
6396 and then Id
/= Attribute_Value_Size
6397 and then not From_At_Mod
(N
)
6399 Error_Msg_N
("cannot specify attribute for subtype", Nam
);
6403 Set_Entity
(N
, U_Ent
);
6405 -- Switch on particular attribute
6413 -- Address attribute definition clause
6415 when Attribute_Address
=> Address
: begin
6417 -- A little error check, catch for X'Address use X'Address;
6419 if Nkind
(Nam
) = N_Identifier
6420 and then Nkind
(Expr
) = N_Attribute_Reference
6421 and then Attribute_Name
(Expr
) = Name_Address
6422 and then Nkind
(Prefix
(Expr
)) = N_Identifier
6423 and then Chars
(Nam
) = Chars
(Prefix
(Expr
))
6426 ("address for & is self-referencing", Prefix
(Expr
), Ent
);
6430 -- Not that special case, carry on with analysis of expression
6432 Analyze_And_Resolve
(Expr
, RTE
(RE_Address
));
6434 -- Even when ignoring rep clauses we need to indicate that the
6435 -- entity has an address clause and thus it is legal to declare
6436 -- it imported. Freeze will get rid of the address clause later.
6437 -- Also call Set_Address_Taken to indicate that an address clause
6438 -- was present, even if we are about to remove it.
6440 if Ignore_Rep_Clauses
then
6441 Set_Address_Taken
(U_Ent
);
6443 if Ekind
(U_Ent
) in E_Variable | E_Constant
then
6444 Record_Rep_Item
(U_Ent
, N
);
6450 if Duplicate_Clause
then
6453 -- Case of address clause for subprogram
6455 elsif Is_Subprogram
(U_Ent
) then
6456 if Has_Homonym
(U_Ent
) then
6458 ("address clause cannot be given for overloaded "
6459 & "subprogram", Nam
);
6463 -- For subprograms, all address clauses are permitted, and we
6464 -- mark the subprogram as having a deferred freeze so that Gigi
6465 -- will not elaborate it too soon.
6467 -- Above needs more comments, what is too soon about???
6469 Set_Has_Delayed_Freeze
(U_Ent
);
6471 -- Case of address clause for entry
6473 elsif Ekind
(U_Ent
) = E_Entry
then
6474 if Nkind
(Parent
(N
)) = N_Task_Body
then
6476 ("entry address must be specified in task spec", Nam
);
6480 -- For entries, we require a constant address
6482 Check_Constant_Address_Clause
(Expr
, U_Ent
);
6484 -- Special checks for task types
6486 if Is_Task_Type
(Scope
(U_Ent
))
6487 and then Comes_From_Source
(Scope
(U_Ent
))
6490 ("??entry address declared for entry in task type", N
);
6492 ("\??only one task can be declared of this type", N
);
6495 -- Entry address clauses are obsolescent
6497 Check_Restriction
(No_Obsolescent_Features
, N
);
6499 if Warn_On_Obsolescent_Feature
then
6501 ("?j?attaching interrupt to task entry is an obsolescent "
6502 & "feature (RM J.7.1)", N
);
6504 ("\?j?use interrupt procedure instead", N
);
6507 -- Case of address clause for an object
6509 elsif Ekind
(U_Ent
) in E_Constant | E_Variable
then
6511 -- Disallow case of an address clause for an object of an
6512 -- indefinite subtype which takes its bounds/discriminant/tag
6513 -- from its initial value. Without this, we get a Gigi
6514 -- assertion failure for things like
6515 -- X : String := Some_Function (...) with Address => ...;
6516 -- where the result subtype of the function is unconstrained.
6518 -- We want to reject two cases: the class-wide case, and the
6519 -- case where the FE conjures up a renaming declaration and
6520 -- would then otherwise generate an address specification for
6521 -- that renaming (which is a malformed tree, which is why Gigi
6524 if Is_Class_Wide_Type
(Etype
(U_Ent
)) then
6526 ("address specification not supported for class-wide " &
6527 "object declaration", Nam
);
6529 elsif Is_Constr_Subt_For_U_Nominal
(Etype
(U_Ent
))
6531 Nkind
(Parent
(U_Ent
)) = N_Object_Renaming_Declaration
6533 -- Confirm accuracy of " and dynamic size" message text
6534 -- before including it. We want to include that text when
6535 -- it is correct because it may be useful to the reader.
6536 -- The case where we omit that part of the message text
6537 -- might be dead code, but let's not rely on that.
6540 ("address specification not supported for object " &
6541 "declaration with indefinite nominal subtype" &
6542 (if Size_Known_At_Compile_Time
(Etype
(U_Ent
))
6544 else " and dynamic size"), Nam
);
6549 Expr
: constant Node_Id
:= Expression
(N
);
6554 -- Exported variables cannot have an address clause, because
6555 -- this cancels the effect of the pragma Export.
6557 if Is_Exported
(U_Ent
) then
6559 ("cannot export object with address clause", Nam
);
6563 Find_Overlaid_Entity
(N
, O_Ent
, Off
);
6565 if Present
(O_Ent
) then
6567 -- If the object overlays a constant object, mark it so
6569 if Is_Constant_Object
(O_Ent
) then
6570 Set_Overlays_Constant
(U_Ent
);
6573 -- If the address clause is of the form:
6575 -- for X'Address use Y'Address;
6579 -- C : constant Address := Y'Address;
6581 -- for X'Address use C;
6583 -- then we make an entry in the table to check the size
6584 -- and alignment of the overlaying variable. But we defer
6585 -- this check till after code generation to take full
6586 -- advantage of the annotation done by the back end.
6588 -- If the entity has a generic type, the check will be
6589 -- performed in the instance if the actual type justifies
6590 -- it, and we do not insert the clause in the table to
6591 -- prevent spurious warnings.
6593 -- Note: we used to test Comes_From_Source and only give
6594 -- this warning for source entities, but we have removed
6595 -- this test. It really seems bogus to generate overlays
6596 -- that would trigger this warning in generated code.
6597 -- Furthermore, by removing the test, we handle the
6598 -- aspect case properly.
6600 if Is_Object
(O_Ent
)
6601 and then not Is_Generic_Formal
(O_Ent
)
6602 and then not Is_Generic_Type
(Etype
(U_Ent
))
6603 and then Address_Clause_Overlay_Warnings
6605 Register_Address_Clause_Check
6606 (N
, U_Ent
, No_Uint
, O_Ent
, Off
);
6609 -- If the overlay changes the storage order, warn since
6610 -- the construct is not really supported by the back end.
6611 -- Also mark the entity as being volatile to block the
6612 -- optimizer, even if there is no warranty on the result.
6614 if (Is_Record_Type
(Etype
(U_Ent
))
6615 or else Is_Array_Type
(Etype
(U_Ent
)))
6616 and then (Is_Record_Type
(Etype
(O_Ent
))
6617 or else Is_Array_Type
(Etype
(O_Ent
)))
6618 and then Reverse_Storage_Order
(Etype
(U_Ent
)) /=
6619 Reverse_Storage_Order
(Etype
(O_Ent
))
6622 ("??overlay changes scalar storage order", Expr
);
6623 Set_Treat_As_Volatile
(U_Ent
);
6627 -- If this is not an overlay, mark a variable as being
6628 -- volatile to prevent unwanted optimizations. It's a
6629 -- conservative interpretation of RM 13.3(19) for the
6630 -- cases where the compiler cannot detect potential
6631 -- aliasing issues easily and it also covers the case
6632 -- of an absolute address where the volatile aspect is
6633 -- kind of implicit.
6635 if Ekind
(U_Ent
) = E_Variable
then
6636 Set_Treat_As_Volatile
(U_Ent
);
6639 -- Make an entry in the table for an absolute address as
6640 -- above to check that the value is compatible with the
6641 -- alignment of the object.
6644 Addr
: constant Node_Id
:= Address_Value
(Expr
);
6646 if Compile_Time_Known_Value
(Addr
)
6647 and then Address_Clause_Overlay_Warnings
6649 Register_Address_Clause_Check
6650 (N
, U_Ent
, Expr_Value
(Addr
), Empty
, False);
6655 -- Issue an unconditional warning for a constant overlaying
6656 -- a variable. For the reverse case, we will issue it only
6657 -- if the variable is modified.
6658 -- Within a generic unit an In_Parameter is a constant.
6659 -- It can be instantiated with a variable, in which case
6660 -- there will be a warning on the instance.
6662 if Ekind
(U_Ent
) = E_Constant
6663 and then Present
(O_Ent
)
6664 and then Ekind
(O_Ent
) /= E_Generic_In_Parameter
6665 and then not Overlays_Constant
(U_Ent
)
6666 and then Address_Clause_Overlay_Warnings
6668 Error_Msg_N
("?o?constant overlays a variable", Expr
);
6670 -- Imported variables can have an address clause, but then
6671 -- the import is pretty meaningless except to suppress
6672 -- initializations, so we do not need such variables to
6673 -- be statically allocated (and in fact it causes trouble
6674 -- if the address clause is a local value).
6676 elsif Is_Imported
(U_Ent
) then
6677 Set_Is_Statically_Allocated
(U_Ent
, False);
6680 -- We mark a possible modification of a variable with an
6681 -- address clause, since it is likely aliasing is occurring.
6683 Note_Possible_Modification
(Nam
, Sure
=> False);
6685 -- Legality checks on the address clause for initialized
6686 -- objects is deferred until the freeze point, because
6687 -- a subsequent pragma might indicate that the object
6688 -- is imported and thus not initialized. Also, the address
6689 -- clause might involve entities that have yet to be
6692 Set_Has_Delayed_Freeze
(U_Ent
);
6694 -- If an initialization call has been generated for this
6695 -- object, it needs to be deferred to after the freeze node
6696 -- we have just now added, otherwise GIGI will see a
6697 -- reference to the variable (as actual to the IP call)
6698 -- before its definition.
6701 Init_Call
: constant Node_Id
:=
6702 Remove_Init_Call
(U_Ent
, N
);
6705 if Present
(Init_Call
) then
6706 Append_Freeze_Action
(U_Ent
, Init_Call
);
6708 -- Reset Initialization_Statements pointer so that
6709 -- if there is a pragma Import further down, it can
6710 -- clear any default initialization.
6712 Set_Initialization_Statements
(U_Ent
, Init_Call
);
6716 -- Entity has delayed freeze, so we will generate an
6717 -- alignment check at the freeze point unless suppressed.
6719 if not Range_Checks_Suppressed
(U_Ent
)
6720 and then not Alignment_Checks_Suppressed
(U_Ent
)
6722 Set_Check_Address_Alignment
(N
);
6725 -- Kill the size check code, since we are not allocating
6726 -- the variable, it is somewhere else.
6728 Kill_Size_Check_Code
(U_Ent
);
6731 -- Not a valid entity for an address clause
6734 Error_Msg_N
("address cannot be given for &", Nam
);
6742 -- Alignment attribute definition clause
6744 when Attribute_Alignment
=> Alignment
: declare
6745 Align
: constant Uint
:= Get_Alignment_Value
(Expr
);
6746 Max_Align
: constant Uint
:= UI_From_Int
(Maximum_Alignment
);
6751 if not Is_Type
(U_Ent
)
6752 and then Ekind
(U_Ent
) /= E_Variable
6753 and then Ekind
(U_Ent
) /= E_Constant
6755 Error_Msg_N
("alignment cannot be given for &", Nam
);
6757 elsif Duplicate_Clause
then
6760 elsif Present
(Align
) then
6761 Set_Has_Alignment_Clause
(U_Ent
);
6763 -- Tagged type case, check for attempt to set alignment to a
6764 -- value greater than Max_Align, and reset if so.
6766 if Is_Tagged_Type
(U_Ent
) and then Align
> Max_Align
then
6768 ("alignment for & set to Maximum_Aligment??", Nam
);
6769 Set_Alignment
(U_Ent
, Max_Align
);
6774 Set_Alignment
(U_Ent
, Align
);
6777 -- For an array type, U_Ent is the first subtype. In that case,
6778 -- also set the alignment of the anonymous base type so that
6779 -- other subtypes (such as the itypes for aggregates of the
6780 -- type) also receive the expected alignment.
6782 if Is_Array_Type
(U_Ent
) then
6783 Set_Alignment
(Base_Type
(U_Ent
), Align
);
6792 -- Bit_Order attribute definition clause
6794 when Attribute_Bit_Order
=>
6795 if not Is_Record_Type
(U_Ent
) then
6797 ("Bit_Order can only be defined for record type", Nam
);
6799 elsif Is_Tagged_Type
(U_Ent
) and then Is_Derived_Type
(U_Ent
) then
6801 ("Bit_Order cannot be defined for record extensions", Nam
);
6803 elsif Duplicate_Clause
then
6807 Analyze_And_Resolve
(Expr
, RTE
(RE_Bit_Order
));
6809 if Etype
(Expr
) = Any_Type
then
6812 elsif not Is_OK_Static_Expression
(Expr
) then
6813 Flag_Non_Static_Expr
6814 ("Bit_Order requires static expression!", Expr
);
6816 elsif (Expr_Value
(Expr
) = 0) /= Bytes_Big_Endian
then
6817 Set_Reverse_Bit_Order
(Base_Type
(U_Ent
), True);
6821 --------------------
6822 -- Component_Size --
6823 --------------------
6825 -- Component_Size attribute definition clause
6827 when Attribute_Component_Size
=> Component_Size_Case
: declare
6828 Csize
: constant Uint
:= Static_Integer
(Expr
);
6832 New_Ctyp
: Entity_Id
;
6836 if not Is_Array_Type
(U_Ent
) then
6837 Error_Msg_N
("component size requires array type", Nam
);
6841 Btype
:= Base_Type
(U_Ent
);
6842 Ctyp
:= Component_Type
(Btype
);
6844 if Duplicate_Clause
then
6847 elsif Rep_Item_Too_Early
(Btype
, N
) then
6850 elsif Present
(Csize
) then
6851 Check_Size
(Expr
, Ctyp
, Csize
, Biased
);
6853 -- For the biased case, build a declaration for a subtype that
6854 -- will be used to represent the biased subtype that reflects
6855 -- the biased representation of components. We need the subtype
6856 -- to get proper conversions on referencing elements of the
6861 Make_Defining_Identifier
(Loc
,
6863 New_External_Name
(Chars
(U_Ent
), 'C', 0, 'T'));
6866 Make_Subtype_Declaration
(Loc
,
6867 Defining_Identifier
=> New_Ctyp
,
6868 Subtype_Indication
=>
6869 New_Occurrence_Of
(Component_Type
(Btype
), Loc
));
6871 Set_Parent
(Decl
, N
);
6872 Analyze
(Decl
, Suppress
=> All_Checks
);
6874 Set_Has_Delayed_Freeze
(New_Ctyp
, False);
6875 Reinit_Esize
(New_Ctyp
);
6876 Set_RM_Size
(New_Ctyp
, Csize
);
6877 Reinit_Alignment
(New_Ctyp
);
6878 Set_Is_Itype
(New_Ctyp
, True);
6879 Set_Associated_Node_For_Itype
(New_Ctyp
, U_Ent
);
6881 Set_Component_Type
(Btype
, New_Ctyp
);
6882 Set_Biased
(New_Ctyp
, N
, "component size clause");
6885 Set_Component_Size
(Btype
, Csize
);
6887 -- Deal with warning on overridden size
6889 if Warn_On_Overridden_Size
6890 and then Has_Size_Clause
(Ctyp
)
6891 and then RM_Size
(Ctyp
) /= Csize
6894 ("component size overrides size clause for&?.s?", N
, Ctyp
);
6897 Set_Has_Component_Size_Clause
(Btype
, True);
6898 Set_Has_Non_Standard_Rep
(Btype
, True);
6900 end Component_Size_Case
;
6902 -----------------------
6903 -- Constant_Indexing --
6904 -----------------------
6906 when Attribute_Constant_Indexing
=>
6907 Check_Indexing_Functions
;
6913 when Attribute_CPU
=>
6914 pragma Assert
(From_Aspect_Specification
(N
));
6915 -- The parser forbids this clause in source code, so it must have
6916 -- come from an aspect specification.
6918 if not Is_Task_Type
(U_Ent
) then
6919 Error_Msg_N
("'C'P'U can only be defined for task", Nam
);
6921 elsif Duplicate_Clause
then
6925 -- The expression must be analyzed in the special manner
6926 -- described in "Handling of Default and Per-Object
6927 -- Expressions" in sem.ads.
6929 -- The visibility to the components must be established
6930 -- and restored before and after analysis.
6933 Preanalyze_Spec_Expression
(Expr
, RTE
(RE_CPU_Range
));
6936 -- AI12-0117-1, "Restriction No_Tasks_Unassigned_To_CPU":
6937 -- If the expression is static, and its value is
6938 -- System.Multiprocessors.Not_A_Specific_CPU (i.e. zero) then
6939 -- that's a violation of No_Tasks_Unassigned_To_CPU. It might
6940 -- seem better to refer to Not_A_Specific_CPU here, but that
6941 -- involves a lot of horsing around with Rtsfind, and this
6942 -- value is not going to change, so it's better to hardwire
6945 -- AI12-0055-1, "All properties of a usage profile are defined
6946 -- by pragmas": If the expression is nonstatic, that's a
6947 -- violation of No_Dynamic_CPU_Assignment.
6949 if Is_OK_Static_Expression
(Expr
) then
6950 if Expr_Value
(Expr
) = Uint_0
then
6951 Check_Restriction
(No_Tasks_Unassigned_To_CPU
, Expr
);
6954 Check_Restriction
(No_Dynamic_CPU_Assignment
, Expr
);
6958 ----------------------
6959 -- Default_Iterator --
6960 ----------------------
6962 when Attribute_Default_Iterator
=> Default_Iterator
: declare
6967 -- If target type is untagged, further checks are irrelevant
6969 if not Is_Tagged_Type
(U_Ent
) then
6971 ("aspect Default_Iterator applies to tagged type", Nam
);
6975 Check_Iterator_Functions
;
6979 if not Is_Entity_Name
(Expr
)
6980 or else Ekind
(Entity
(Expr
)) /= E_Function
6982 Error_Msg_N
("aspect Iterator must be a function", Expr
);
6985 Func
:= Entity
(Expr
);
6988 -- The type of the first parameter must be T, T'class, or a
6989 -- corresponding access type (5.5.1 (8/3). If function is
6990 -- parameterless label type accordingly.
6992 if No
(First_Formal
(Func
)) then
6995 Typ
:= Etype
(First_Formal
(Func
));
6999 or else Typ
= Class_Wide_Type
(U_Ent
)
7000 or else (Is_Access_Type
(Typ
)
7001 and then Designated_Type
(Typ
) = U_Ent
)
7002 or else (Is_Access_Type
(Typ
)
7003 and then Designated_Type
(Typ
) =
7004 Class_Wide_Type
(U_Ent
))
7010 ("Default_Iterator must be a primitive of&", Func
, U_Ent
);
7012 end Default_Iterator
;
7014 ------------------------
7015 -- Dispatching_Domain --
7016 ------------------------
7018 when Attribute_Dispatching_Domain
=>
7019 pragma Assert
(From_Aspect_Specification
(N
));
7020 -- The parser forbids this clause in source code, so it must have
7021 -- come from an aspect specification.
7023 if not Is_Task_Type
(U_Ent
) then
7025 ("Dispatching_Domain can only be defined for task", Nam
);
7027 elsif Duplicate_Clause
then
7031 -- The expression must be analyzed in the special manner
7032 -- described in "Handling of Default and Per-Object
7033 -- Expressions" in sem.ads.
7035 -- The visibility to the components must be restored
7039 Preanalyze_Spec_Expression
7040 (Expr
, RTE
(RE_Dispatching_Domain
));
7049 when Attribute_External_Tag
=>
7050 if not Is_Tagged_Type
(U_Ent
) then
7051 Error_Msg_N
("should be a tagged type", Nam
);
7054 if Duplicate_Clause
then
7058 Analyze_And_Resolve
(Expr
, Standard_String
);
7060 if not Is_OK_Static_Expression
(Expr
) then
7061 Flag_Non_Static_Expr
7062 ("static string required for tag name!", Nam
);
7065 if not Is_Library_Level_Entity
(U_Ent
) then
7067 ("??non-unique external tag supplied for &", N
, U_Ent
);
7069 ("\??same external tag applies to all subprogram calls",
7072 ("\??corresponding internal tag cannot be obtained", N
);
7076 --------------------------
7077 -- Implicit_Dereference --
7078 --------------------------
7080 when Attribute_Implicit_Dereference
=>
7082 -- Legality checks already performed at the point of the type
7083 -- declaration, aspect is not delayed.
7091 when Attribute_Input
=>
7092 Analyze_Stream_TSS_Definition
(TSS_Stream_Input
);
7093 Set_Has_Specified_Stream_Input
(Ent
);
7095 ------------------------
7096 -- Interrupt_Priority --
7097 ------------------------
7099 when Attribute_Interrupt_Priority
=>
7100 pragma Assert
(From_Aspect_Specification
(N
));
7101 -- The parser forbids this clause in source code, so it must have
7102 -- come from an aspect specification.
7104 if not Is_Concurrent_Type
(U_Ent
) then
7106 ("Interrupt_Priority can only be defined for task and "
7107 & "protected object", Nam
);
7109 elsif Duplicate_Clause
then
7113 -- The expression must be analyzed in the special manner
7114 -- described in "Handling of Default and Per-Object
7115 -- Expressions" in sem.ads.
7117 -- The visibility to the components must be restored
7121 Preanalyze_Spec_Expression
7122 (Expr
, RTE
(RE_Interrupt_Priority
));
7126 -- Check the No_Task_At_Interrupt_Priority restriction
7128 if Is_Task_Type
(U_Ent
) then
7129 Check_Restriction
(No_Task_At_Interrupt_Priority
, N
);
7137 when Attribute_Iterable
=>
7140 if Nkind
(Expr
) /= N_Aggregate
then
7141 Error_Msg_N
("aspect Iterable must be an aggregate", Expr
);
7149 Assoc
:= First
(Component_Associations
(Expr
));
7150 while Present
(Assoc
) loop
7151 Analyze
(Expression
(Assoc
));
7153 if not Is_Entity_Name
(Expression
(Assoc
))
7154 or else Ekind
(Entity
(Expression
(Assoc
))) /= E_Function
7156 Error_Msg_N
("value must be a function", Assoc
);
7163 ----------------------
7164 -- Iterator_Element --
7165 ----------------------
7167 when Attribute_Iterator_Element
=>
7170 if not Is_Entity_Name
(Expr
)
7171 or else not Is_Type
(Entity
(Expr
))
7173 Error_Msg_N
("aspect Iterator_Element must be a type", Expr
);
7181 -- Machine radix attribute definition clause
7183 when Attribute_Machine_Radix
=> Machine_Radix
: declare
7184 Radix
: constant Uint
:= Static_Integer
(Expr
);
7187 if not Is_Decimal_Fixed_Point_Type
(U_Ent
) then
7188 Error_Msg_N
("decimal fixed-point type expected for &", Nam
);
7190 elsif Duplicate_Clause
then
7193 elsif Present
(Radix
) then
7194 Set_Has_Machine_Radix_Clause
(U_Ent
);
7195 Set_Has_Non_Standard_Rep
(Base_Type
(U_Ent
));
7200 elsif Radix
= 10 then
7201 Set_Machine_Radix_10
(U_Ent
);
7204 Error_Msg_N
("machine radix value must be 2 or 10", Expr
);
7213 -- Object_Size attribute definition clause
7215 when Attribute_Object_Size
=> Object_Size
: declare
7216 Size
: constant Uint
:= Static_Integer
(Expr
);
7219 pragma Warnings
(Off
, Biased
);
7222 if not Is_Type
(U_Ent
) then
7223 Error_Msg_N
("Object_Size cannot be given for &", Nam
);
7225 elsif Duplicate_Clause
then
7229 Check_Size
(Expr
, U_Ent
, Size
, Biased
);
7231 if No
(Size
) or else Size
<= 0 then
7232 Error_Msg_N
("Object_Size must be positive", Expr
);
7234 elsif Is_Scalar_Type
(U_Ent
) then
7235 if Size
/= 8 and then Size
/= 16 and then Size
/= 32
7236 and then UI_Mod
(Size
, 64) /= 0
7239 ("Object_Size must be 8, 16, 32, or multiple of 64",
7243 elsif Size
mod 8 /= 0 then
7244 Error_Msg_N
("Object_Size must be a multiple of 8", Expr
);
7247 Set_Esize
(U_Ent
, Size
);
7248 Set_Has_Object_Size_Clause
(U_Ent
);
7249 Alignment_Check_For_Size_Change
(U_Ent
, Size
);
7257 when Attribute_Output
=>
7258 Analyze_Stream_TSS_Definition
(TSS_Stream_Output
);
7259 Set_Has_Specified_Stream_Output
(Ent
);
7265 when Attribute_Priority
=>
7267 -- Priority attribute definition clause not allowed except from
7268 -- aspect specification.
7270 if From_Aspect_Specification
(N
) then
7271 if not (Is_Concurrent_Type
(U_Ent
)
7272 or else Ekind
(U_Ent
) = E_Procedure
)
7275 ("Priority can only be defined for task and protected "
7278 elsif Duplicate_Clause
then
7282 -- The expression must be analyzed in the special manner
7283 -- described in "Handling of Default and Per-Object
7284 -- Expressions" in sem.ads.
7286 -- The visibility to the components must be restored
7289 Preanalyze_Spec_Expression
(Expr
, Standard_Integer
);
7292 if not Is_OK_Static_Expression
(Expr
) then
7293 Check_Restriction
(Static_Priorities
, Expr
);
7299 ("attribute& cannot be set with definition clause", N
);
7306 when Attribute_Put_Image
=>
7307 Analyze_Put_Image_TSS_Definition
;
7313 when Attribute_Read
=>
7314 Analyze_Stream_TSS_Definition
(TSS_Stream_Read
);
7315 Set_Has_Specified_Stream_Read
(Ent
);
7317 --------------------------
7318 -- Scalar_Storage_Order --
7319 --------------------------
7321 -- Scalar_Storage_Order attribute definition clause
7323 when Attribute_Scalar_Storage_Order
=>
7324 if not (Is_Record_Type
(U_Ent
) or else Is_Array_Type
(U_Ent
)) then
7326 ("Scalar_Storage_Order can only be defined for record or "
7327 & "array type", Nam
);
7329 elsif Duplicate_Clause
then
7333 Analyze_And_Resolve
(Expr
, RTE
(RE_Bit_Order
));
7335 if Etype
(Expr
) = Any_Type
then
7338 elsif not Is_OK_Static_Expression
(Expr
) then
7339 Flag_Non_Static_Expr
7340 ("Scalar_Storage_Order requires static expression!", Expr
);
7342 elsif (Expr_Value
(Expr
) = 0) /= Bytes_Big_Endian
then
7344 -- Here for the case of a non-default (i.e. non-confirming)
7345 -- Scalar_Storage_Order attribute definition.
7347 if Support_Nondefault_SSO_On_Target
then
7348 Set_Reverse_Storage_Order
(Base_Type
(U_Ent
), True);
7351 ("non-default Scalar_Storage_Order not supported on "
7356 -- Clear SSO default indications since explicit setting of the
7357 -- order overrides the defaults.
7359 Set_SSO_Set_Low_By_Default
(Base_Type
(U_Ent
), False);
7360 Set_SSO_Set_High_By_Default
(Base_Type
(U_Ent
), False);
7363 ------------------------
7364 -- Size or Value_Size --
7365 ------------------------
7367 -- Size or Value_Size attribute definition clause. These are treated
7368 -- the same, except that Size is allowed on objects, and Value_Size
7369 -- is allowed on nonfirst subtypes. First subtypes allow both Size
7370 -- and Value_Size; the treatment is the same for both.
7372 when Attribute_Size | Attribute_Value_Size
=> Size
: declare
7373 Size
: constant Uint
:= Static_Integer
(Expr
);
7375 Attr_Name
: constant String :=
7376 (if Id
= Attribute_Size
then "size"
7377 elsif Id
= Attribute_Value_Size
then "value size"
7378 else ""); -- can't happen
7379 -- Name of the attribute for printing in messages
7381 OK_Prefix
: constant Boolean :=
7382 (if Id
= Attribute_Size
then
7383 Ekind
(U_Ent
) in Type_Kind | Constant_Or_Variable_Kind
7384 elsif Id
= Attribute_Value_Size
then
7385 Ekind
(U_Ent
) in Type_Kind
7386 else False); -- can't happen
7387 -- For X'Size, X can be a type or object; for X'Value_Size,
7388 -- X can be a type. Note that we already checked that 'Size
7389 -- can be specified only for a first subtype.
7394 if not OK_Prefix
then
7395 Error_Msg_N
(Attr_Name
& " cannot be given for &", Nam
);
7397 elsif Duplicate_Clause
then
7400 elsif Is_Array_Type
(U_Ent
)
7401 and then not Is_Constrained
(U_Ent
)
7404 (Attr_Name
& " cannot be given for unconstrained array", Nam
);
7406 elsif Present
(Size
) then
7408 Etyp
: constant Entity_Id
:=
7409 (if Is_Type
(U_Ent
) then U_Ent
else Etype
(U_Ent
));
7412 -- Check size, note that Gigi is in charge of checking that
7413 -- the size of an array or record type is OK. Also we do not
7414 -- check the size in the ordinary fixed-point case, since
7415 -- it is too early to do so (there may be subsequent small
7416 -- clause that affects the size). We can check the size if
7417 -- a small clause has already been given.
7419 if not Is_Ordinary_Fixed_Point_Type
(U_Ent
)
7420 or else Has_Small_Clause
(U_Ent
)
7425 Check_Size
(Expr
, Etyp
, Size
, Biased
);
7426 Set_Biased
(U_Ent
, N
, Attr_Name
& " clause", Biased
);
7430 -- For types, set RM_Size and Esize if appropriate
7432 if Is_Type
(U_Ent
) then
7433 Set_RM_Size
(U_Ent
, Size
);
7435 -- If we are specifying the Size or Value_Size of a
7436 -- first subtype, then for elementary types, increase
7437 -- Object_Size to power of 2, but not less than a storage
7438 -- unit in any case (normally this means it will be byte
7441 -- For all other types, nothing else to do, we leave
7442 -- Esize (object size) unset; the back end will set it
7443 -- from the size and alignment in an appropriate manner.
7445 -- In both cases, we check whether the alignment must be
7446 -- reset in the wake of the size change.
7448 -- For nonfirst subtypes ('Value_Size only), we do
7451 if Is_First_Subtype
(U_Ent
) then
7452 if Is_Elementary_Type
(U_Ent
) then
7453 if Size
<= System_Storage_Unit
then
7455 (U_Ent
, UI_From_Int
(System_Storage_Unit
));
7456 elsif Size
<= 16 then
7457 Set_Esize
(U_Ent
, Uint_16
);
7458 elsif Size
<= 32 then
7459 Set_Esize
(U_Ent
, Uint_32
);
7461 Set_Esize
(U_Ent
, (Size
+ 63) / 64 * 64);
7464 Alignment_Check_For_Size_Change
7465 (U_Ent
, Esize
(U_Ent
));
7467 Alignment_Check_For_Size_Change
(U_Ent
, Size
);
7471 -- For Object'Size, set Esize only
7474 if Is_Elementary_Type
(Etyp
)
7475 and then Size
/= System_Storage_Unit
7479 and then Size
/= System_Max_Integer_Size
7481 Error_Msg_Uint_1
:= UI_From_Int
(System_Storage_Unit
);
7483 UI_From_Int
(System_Max_Integer_Size
);
7485 ("size for primitive object must be a power of 2 in "
7486 & "the range ^-^", N
);
7489 Set_Esize
(U_Ent
, Size
);
7492 -- As of RM 13.1, only confirming size
7493 -- (i.e. (Size = Esize (Etyp))) for aliased object of
7494 -- elementary type must be supported.
7495 -- GNAT rejects nonconfirming size for such object.
7497 if Is_Aliased
(U_Ent
)
7498 and then Is_Elementary_Type
(Etyp
)
7499 and then Known_Esize
(U_Ent
)
7500 and then Size
/= Esize
(Etyp
)
7503 ("nonconfirming Size for aliased object is not "
7507 Set_Has_Size_Clause
(U_Ent
);
7516 -- Small attribute definition clause
7518 when Attribute_Small
=> Small
: declare
7519 Implicit_Base
: constant Entity_Id
:= Base_Type
(U_Ent
);
7523 Analyze_And_Resolve
(Expr
, Any_Real
);
7525 if Etype
(Expr
) = Any_Type
then
7528 elsif not Is_OK_Static_Expression
(Expr
) then
7529 Flag_Non_Static_Expr
7530 ("small requires static expression!", Expr
);
7534 Small
:= Expr_Value_R
(Expr
);
7536 if Small
<= Ureal_0
then
7537 Error_Msg_N
("small value must be greater than zero", Expr
);
7543 if not Is_Ordinary_Fixed_Point_Type
(U_Ent
) then
7545 ("small requires an ordinary fixed point type", Nam
);
7547 elsif Has_Small_Clause
(U_Ent
) then
7548 Error_Msg_N
("small already given for &", Nam
);
7550 elsif Small
> Delta_Value
(U_Ent
) then
7552 ("small value must not be greater than delta value", Nam
);
7555 Set_Small_Value
(U_Ent
, Small
);
7556 Set_Small_Value
(Implicit_Base
, Small
);
7557 Set_Has_Small_Clause
(U_Ent
);
7558 Set_Has_Small_Clause
(Implicit_Base
);
7559 Set_Has_Non_Standard_Rep
(Implicit_Base
);
7567 -- Storage_Pool attribute definition clause
7569 when Attribute_Simple_Storage_Pool
7570 | Attribute_Storage_Pool
7572 Storage_Pool
: declare
7576 procedure Associate_Storage_Pool
7577 (Ent
: Entity_Id
; Pool
: Entity_Id
);
7578 -- Associate Pool to Ent and perform legality checks on subpools
7580 ----------------------------
7581 -- Associate_Storage_Pool --
7582 ----------------------------
7584 procedure Associate_Storage_Pool
7585 (Ent
: Entity_Id
; Pool
: Entity_Id
)
7587 function Object_From
(Pool
: Entity_Id
) return Entity_Id
;
7588 -- Return the entity of which Pool is a part of
7594 function Object_From
7595 (Pool
: Entity_Id
) return Entity_Id
7597 N
: Node_Id
:= Pool
;
7599 if Present
(Renamed_Object
(Pool
)) then
7600 N
:= Renamed_Object
(Pool
);
7603 while Present
(N
) loop
7605 when N_Defining_Identifier
=>
7608 when N_Identifier | N_Expanded_Name
=>
7611 when N_Indexed_Component | N_Selected_Component |
7612 N_Explicit_Dereference
7616 when N_Type_Conversion
=>
7617 N
:= Expression
(N
);
7620 -- ??? we probably should handle more cases but
7621 -- this is good enough in practice for this check
7622 -- on a corner case.
7634 Set_Associated_Storage_Pool
(Ent
, Pool
);
7636 -- Check RM 13.11.4(22-23/3): a specification of a storage pool
7637 -- is illegal if the storage pool supports subpools and:
7638 -- (A) The access type is a general access type.
7639 -- (B) The access type is statically deeper than the storage
7641 -- (C) The storage pool object is a part of a formal parameter;
7642 -- (D) The storage pool object is a part of the dereference of
7643 -- a non-library level general access type;
7645 if Ada_Version
>= Ada_2012
7646 and then RTU_Loaded
(System_Storage_Pools_Subpools
)
7648 Is_Ancestor
(RTE
(RE_Root_Storage_Pool_With_Subpools
),
7653 if Ekind
(Etype
(Ent
)) = E_General_Access_Type
then
7655 ("subpool cannot be used on general access type", Ent
);
7660 if Type_Access_Level
(Ent
)
7661 > Static_Accessibility_Level
7662 (Pool
, Object_Decl_Level
)
7665 ("subpool access type has deeper accessibility "
7666 & "level than pool", Ent
);
7670 Obj
:= Object_From
(Pool
);
7674 if Present
(Obj
) and then Is_Formal
(Obj
) then
7676 ("subpool cannot be part of a parameter", Ent
);
7683 and then Ekind
(Etype
(Obj
)) = E_General_Access_Type
7684 and then not Is_Library_Level_Entity
(Etype
(Obj
))
7687 ("subpool cannot be part of the dereference of a " &
7688 "nested general access type", Ent
);
7692 end Associate_Storage_Pool
;
7695 if Ekind
(U_Ent
) = E_Access_Subprogram_Type
then
7697 ("storage pool cannot be given for access-to-subprogram type",
7701 elsif Ekind
(U_Ent
) not in E_Access_Type | E_General_Access_Type
7704 ("storage pool can only be given for access types", Nam
);
7707 elsif Is_Derived_Type
(U_Ent
) then
7709 ("storage pool cannot be given for a derived access type",
7712 elsif Duplicate_Clause
then
7715 elsif Present
(Associated_Storage_Pool
(U_Ent
)) then
7716 Error_Msg_N
("storage pool already given for &", Nam
);
7720 -- Check for Storage_Size previously given
7723 SS
: constant Node_Id
:=
7724 Get_Attribute_Definition_Clause
7725 (U_Ent
, Attribute_Storage_Size
);
7727 if Present
(SS
) then
7728 Check_Pool_Size_Clash
(U_Ent
, N
, SS
);
7732 -- Storage_Pool case
7734 if Id
= Attribute_Storage_Pool
then
7736 (Expr
, Class_Wide_Type
(RTE
(RE_Root_Storage_Pool
)));
7738 -- In the Simple_Storage_Pool case, we allow a variable of any
7739 -- simple storage pool type, so we Resolve without imposing an
7743 Analyze_And_Resolve
(Expr
);
7745 if No
(Get_Rep_Pragma
7746 (Etype
(Expr
), Name_Simple_Storage_Pool_Type
))
7749 ("expression must be of a simple storage pool type", Expr
);
7753 if not Denotes_Variable
(Expr
) then
7754 Error_Msg_N
("storage pool must be a variable", Expr
);
7758 if Nkind
(Expr
) = N_Type_Conversion
then
7759 T
:= Etype
(Expression
(Expr
));
7764 -- The Stack_Bounded_Pool is used internally for implementing
7765 -- access types with a Storage_Size. Since it only work properly
7766 -- when used on one specific type, we need to check that it is not
7767 -- hijacked improperly:
7769 -- type T is access Integer;
7770 -- for T'Storage_Size use n;
7771 -- type Q is access Float;
7772 -- for Q'Storage_Size use T'Storage_Size; -- incorrect
7774 if Is_RTE
(Base_Type
(T
), RE_Stack_Bounded_Pool
) then
7775 Error_Msg_N
("non-shareable internal Pool", Expr
);
7779 -- Validate_Remote_Access_To_Class_Wide_Type for attribute
7780 -- Storage_Pool since this attribute cannot be defined for such
7781 -- types (RM E.2.2(17)).
7783 Validate_Remote_Access_To_Class_Wide_Type
(N
);
7785 -- If the argument is a name that is not an entity name, then
7786 -- we construct a renaming operation to define an entity of
7787 -- type storage pool.
7789 if not Is_Entity_Name
(Expr
)
7790 and then Is_Object_Reference
(Expr
)
7792 Pool
:= Make_Temporary
(Loc
, 'P', Expr
);
7795 Rnode
: constant Node_Id
:=
7796 Make_Object_Renaming_Declaration
(Loc
,
7797 Defining_Identifier
=> Pool
,
7799 New_Occurrence_Of
(Etype
(Expr
), Loc
),
7803 -- If the attribute definition clause comes from an aspect
7804 -- clause, then insert the renaming before the associated
7805 -- entity's declaration, since the attribute clause has
7806 -- not yet been appended to the declaration list.
7808 if From_Aspect_Specification
(N
) then
7809 Insert_Before
(Parent
(Entity
(N
)), Rnode
);
7811 Insert_Before
(N
, Rnode
);
7815 Associate_Storage_Pool
(U_Ent
, Pool
);
7818 elsif Is_Entity_Name
(Expr
) then
7819 Pool
:= Entity
(Expr
);
7821 -- If pool is a renamed object, get original one. This can
7822 -- happen with an explicit renaming, and within instances.
7824 while Present
(Renamed_Object
(Pool
))
7825 and then Is_Entity_Name
(Renamed_Object
(Pool
))
7827 Pool
:= Entity
(Renamed_Object
(Pool
));
7830 if Present
(Renamed_Object
(Pool
))
7831 and then Nkind
(Renamed_Object
(Pool
)) = N_Type_Conversion
7832 and then Is_Entity_Name
(Expression
(Renamed_Object
(Pool
)))
7834 Pool
:= Entity
(Expression
(Renamed_Object
(Pool
)));
7837 Associate_Storage_Pool
(U_Ent
, Pool
);
7839 elsif Nkind
(Expr
) = N_Type_Conversion
7840 and then Is_Entity_Name
(Expression
(Expr
))
7841 and then Nkind
(Original_Node
(Expr
)) = N_Attribute_Reference
7843 Pool
:= Entity
(Expression
(Expr
));
7844 Associate_Storage_Pool
(U_Ent
, Pool
);
7847 Error_Msg_N
("incorrect reference to a Storage Pool", Expr
);
7856 -- Storage_Size attribute definition clause
7858 when Attribute_Storage_Size
=> Storage_Size
: declare
7859 Btype
: constant Entity_Id
:= Base_Type
(U_Ent
);
7862 if Is_Task_Type
(U_Ent
) then
7864 -- Check obsolescent (but never obsolescent if from aspect)
7866 if not From_Aspect_Specification
(N
) then
7867 Check_Restriction
(No_Obsolescent_Features
, N
);
7869 if Warn_On_Obsolescent_Feature
then
7871 ("?j?storage size clause for task is an obsolescent "
7872 & "feature (RM J.9)", N
);
7873 Error_Msg_N
("\?j?use Storage_Size pragma instead", N
);
7880 if not Is_Access_Type
(U_Ent
)
7881 and then Ekind
(U_Ent
) /= E_Task_Type
7883 Error_Msg_N
("storage size cannot be given for &", Nam
);
7885 elsif Is_Access_Type
(U_Ent
) and Is_Derived_Type
(U_Ent
) then
7887 ("storage size cannot be given for a derived access type",
7890 elsif Duplicate_Clause
then
7894 -- Validate_Remote_Access_To_Class_Wide_Type for attribute
7895 -- Storage_Size since this attribute cannot be defined for such
7896 -- types (RM E.2.2(17)).
7898 Validate_Remote_Access_To_Class_Wide_Type
(N
);
7900 Analyze_And_Resolve
(Expr
, Any_Integer
);
7902 if Is_Access_Type
(U_Ent
) then
7904 -- Check for Storage_Pool previously given
7907 SP
: constant Node_Id
:=
7908 Get_Attribute_Definition_Clause
7909 (U_Ent
, Attribute_Storage_Pool
);
7912 if Present
(SP
) then
7913 Check_Pool_Size_Clash
(U_Ent
, SP
, N
);
7917 -- Special case of for x'Storage_Size use 0
7919 if Is_OK_Static_Expression
(Expr
)
7920 and then Expr_Value
(Expr
) = 0
7922 Set_No_Pool_Assigned
(Btype
);
7926 Set_Has_Storage_Size_Clause
(Btype
);
7934 when Attribute_Stream_Size
=> Stream_Size
: declare
7935 Size
: constant Uint
:= Static_Integer
(Expr
);
7938 if Ada_Version
<= Ada_95
then
7939 Check_Restriction
(No_Implementation_Attributes
, N
);
7942 if Duplicate_Clause
then
7945 elsif Is_Elementary_Type
(U_Ent
) then
7946 -- Size will be empty if we already detected an error
7947 -- (e.g. Expr is of the wrong type); we might as well
7948 -- give the useful hint below even in that case.
7950 if No
(Size
) or else
7951 (Size
/= System_Storage_Unit
7952 and then Size
/= System_Storage_Unit
* 2
7953 and then Size
/= System_Storage_Unit
* 3
7954 and then Size
/= System_Storage_Unit
* 4
7955 and then Size
/= System_Storage_Unit
* 8)
7958 ("stream size for elementary type must be 8, 16, 24, " &
7961 elsif Known_RM_Size
(U_Ent
) and then RM_Size
(U_Ent
) > Size
then
7962 Error_Msg_Uint_1
:= RM_Size
(U_Ent
);
7964 ("stream size for elementary type must be 8, 16, 24, " &
7965 "32 or 64 and at least ^", N
);
7968 Set_Has_Stream_Size_Clause
(U_Ent
);
7971 Error_Msg_N
("Stream_Size cannot be given for &", Nam
);
7975 -----------------------
7976 -- Variable_Indexing --
7977 -----------------------
7979 when Attribute_Variable_Indexing
=>
7980 Check_Indexing_Functions
;
7986 when Attribute_Write
=>
7987 Analyze_Stream_TSS_Definition
(TSS_Stream_Write
);
7988 Set_Has_Specified_Stream_Write
(Ent
);
7990 -- All other attributes cannot be set
7994 ("attribute& cannot be set with definition clause", N
);
7997 -- The test for the type being frozen must be performed after any
7998 -- expression the clause has been analyzed since the expression itself
7999 -- might cause freezing that makes the clause illegal.
8001 if Rep_Item_Too_Late
(U_Ent
, N
, FOnly
) then
8004 end Analyze_Attribute_Definition_Clause
;
8006 ----------------------------
8007 -- Analyze_Code_Statement --
8008 ----------------------------
8010 procedure Analyze_Code_Statement
(N
: Node_Id
) is
8011 HSS
: constant Node_Id
:= Parent
(N
);
8012 SBody
: constant Node_Id
:= Parent
(HSS
);
8013 Subp
: constant Entity_Id
:= Current_Scope
;
8020 -- Accept foreign code statements for CodePeer. The analysis is skipped
8021 -- to avoid rejecting unrecognized constructs.
8023 if CodePeer_Mode
then
8028 -- Analyze and check we get right type, note that this implements the
8029 -- requirement (RM 13.8(1)) that Machine_Code be with'ed, since that is
8030 -- the only way that Asm_Insn could possibly be visible.
8032 Analyze_And_Resolve
(Expression
(N
));
8034 if Etype
(Expression
(N
)) = Any_Type
then
8036 elsif not Is_RTE
(Etype
(Expression
(N
)), RE_Asm_Insn
) then
8037 Error_Msg_N
("incorrect type for code statement", N
);
8041 Check_Code_Statement
(N
);
8043 -- Make sure we appear in the handled statement sequence of a subprogram
8046 if Nkind
(HSS
) /= N_Handled_Sequence_Of_Statements
8047 or else Nkind
(SBody
) /= N_Subprogram_Body
8050 ("code statement can only appear in body of subprogram", N
);
8054 -- Do remaining checks (RM 13.8(3)) if not already done
8056 if not Is_Machine_Code_Subprogram
(Subp
) then
8057 Set_Is_Machine_Code_Subprogram
(Subp
);
8059 -- No exception handlers allowed
8061 if Present
(Exception_Handlers
(HSS
)) then
8063 ("exception handlers not permitted in machine code subprogram",
8064 First
(Exception_Handlers
(HSS
)));
8067 -- No declarations other than use clauses and pragmas (we allow
8068 -- certain internally generated declarations as well).
8070 Decl
:= First
(Declarations
(SBody
));
8071 while Present
(Decl
) loop
8072 DeclO
:= Original_Node
(Decl
);
8073 if Comes_From_Source
(DeclO
)
8074 and Nkind
(DeclO
) not in N_Pragma
8075 | N_Use_Package_Clause
8077 | N_Implicit_Label_Declaration
8080 ("this declaration is not allowed in machine code subprogram",
8087 -- No statements other than code statements, pragmas, and labels.
8088 -- Again we allow certain internally generated statements.
8090 -- In Ada 2012, qualified expressions are names, and the code
8091 -- statement is initially parsed as a procedure call.
8093 Stmt
:= First
(Statements
(HSS
));
8094 while Present
(Stmt
) loop
8095 StmtO
:= Original_Node
(Stmt
);
8097 -- A procedure call transformed into a code statement is OK
8099 if Ada_Version
>= Ada_2012
8100 and then Nkind
(StmtO
) = N_Procedure_Call_Statement
8101 and then Nkind
(Name
(StmtO
)) = N_Qualified_Expression
8105 elsif Comes_From_Source
(StmtO
)
8106 and then Nkind
(StmtO
) not in
8107 N_Pragma | N_Label | N_Code_Statement
8110 ("this statement is not allowed in machine code subprogram",
8117 end Analyze_Code_Statement
;
8119 -----------------------------------------------
8120 -- Analyze_Enumeration_Representation_Clause --
8121 -----------------------------------------------
8123 procedure Analyze_Enumeration_Representation_Clause
(N
: Node_Id
) is
8124 Ident
: constant Node_Id
:= Identifier
(N
);
8125 Aggr
: constant Node_Id
:= Array_Aggregate
(N
);
8126 Enumtype
: Entity_Id
;
8133 Err
: Boolean := False;
8134 -- Set True to avoid cascade errors and crashes on incorrect source code
8136 Lo
: constant Uint
:= Expr_Value
(Type_Low_Bound
(Universal_Integer
));
8137 Hi
: constant Uint
:= Expr_Value
(Type_High_Bound
(Universal_Integer
));
8138 -- Allowed range of universal integer (= allowed range of enum lit vals)
8142 -- Minimum and maximum values of entries
8144 Max_Node
: Node_Id
:= Empty
; -- init to avoid warning
8145 -- Pointer to node for literal providing max value
8148 if Ignore_Rep_Clauses
then
8149 Kill_Rep_Clause
(N
);
8153 -- Ignore enumeration rep clauses by default in CodePeer mode,
8154 -- unless -gnatd.I is specified, as a work around for potential false
8155 -- positive messages.
8157 if CodePeer_Mode
and not Debug_Flag_Dot_II
then
8161 -- First some basic error checks
8164 Enumtype
:= Entity
(Ident
);
8166 if Enumtype
= Any_Type
8167 or else Rep_Item_Too_Early
(Enumtype
, N
)
8171 Enumtype
:= Underlying_Type
(Enumtype
);
8174 if not Is_Enumeration_Type
(Enumtype
) then
8176 ("enumeration type required, found}",
8177 Ident
, First_Subtype
(Enumtype
));
8181 -- Ignore rep clause on generic actual type. This will already have
8182 -- been flagged on the template as an error, and this is the safest
8183 -- way to ensure we don't get a junk cascaded message in the instance.
8185 if Is_Generic_Actual_Type
(Enumtype
) then
8188 -- Type must be in current scope
8190 elsif Scope
(Enumtype
) /= Current_Scope
then
8191 Error_Msg_N
("type must be declared in this scope", Ident
);
8194 -- Type must be a first subtype
8196 elsif not Is_First_Subtype
(Enumtype
) then
8197 Error_Msg_N
("cannot give enumeration rep clause for subtype", N
);
8200 -- Ignore duplicate rep clause
8202 elsif Has_Enumeration_Rep_Clause
(Enumtype
) then
8203 Error_Msg_N
("duplicate enumeration rep clause ignored", N
);
8206 -- Don't allow rep clause for standard [wide_[wide_]]character
8208 elsif Is_Standard_Character_Type
(Enumtype
) then
8209 Error_Msg_N
("enumeration rep clause not allowed for this type", N
);
8212 -- Check that the expression is a proper aggregate (no parentheses)
8214 elsif Paren_Count
(Aggr
) /= 0 then
8216 ("extra parentheses surrounding aggregate not allowed", Aggr
);
8219 -- Reject the mixing of named and positional entries in the aggregate
8221 elsif Present
(Expressions
(Aggr
))
8222 and then Present
(Component_Associations
(Aggr
))
8224 Error_Msg_N
("cannot mix positional and named entries in "
8225 & "enumeration rep clause", N
);
8228 -- All tests passed, so set rep clause in place
8231 Set_Has_Enumeration_Rep_Clause
(Enumtype
);
8232 Set_Has_Enumeration_Rep_Clause
(Base_Type
(Enumtype
));
8235 -- Now we process the aggregate. Note that we don't use the normal
8236 -- aggregate code for this purpose, because we don't want any of the
8237 -- normal expansion activities, and a number of special semantic
8238 -- rules apply (including the component type being any integer type)
8240 Elit
:= First_Literal
(Enumtype
);
8242 -- Process positional entries
8244 if Present
(Expressions
(Aggr
)) then
8245 Expr
:= First
(Expressions
(Aggr
));
8246 while Present
(Expr
) loop
8248 Error_Msg_N
("too many entries in aggregate", Expr
);
8252 Val
:= Static_Integer
(Expr
);
8254 -- Err signals that we found some incorrect entries processing
8255 -- the list. The final checks for completeness and ordering are
8256 -- skipped in this case.
8261 elsif Val
< Lo
or else Hi
< Val
then
8262 Error_Msg_N
("value outside permitted range", Expr
);
8266 Set_Enumeration_Rep
(Elit
, Val
);
8267 Set_Enumeration_Rep_Expr
(Elit
, Expr
);
8274 -- Process named entries
8276 elsif Present
(Component_Associations
(Aggr
)) then
8277 Assoc
:= First
(Component_Associations
(Aggr
));
8278 while Present
(Assoc
) loop
8279 Choice
:= First
(Choices
(Assoc
));
8281 if Present
(Next
(Choice
)) then
8283 ("multiple choice not allowed here", Next
(Choice
));
8287 if Nkind
(Choice
) = N_Others_Choice
then
8288 Error_Msg_N
("OTHERS choice not allowed here", Choice
);
8291 elsif Nkind
(Choice
) = N_Range
then
8293 -- ??? should allow zero/one element range here
8295 Error_Msg_N
("range not allowed here", Choice
);
8299 Analyze_And_Resolve
(Choice
, Enumtype
);
8301 if Error_Posted
(Choice
) then
8306 if Is_Entity_Name
(Choice
)
8307 and then Is_Type
(Entity
(Choice
))
8309 Error_Msg_N
("subtype name not allowed here", Choice
);
8312 -- ??? should allow static subtype with zero/one entry
8314 elsif Etype
(Choice
) = Base_Type
(Enumtype
) then
8315 if not Is_OK_Static_Expression
(Choice
) then
8316 Flag_Non_Static_Expr
8317 ("non-static expression used for choice!", Choice
);
8321 Elit
:= Expr_Value_E
(Choice
);
8323 if Present
(Enumeration_Rep_Expr
(Elit
)) then
8325 Sloc
(Enumeration_Rep_Expr
(Elit
));
8327 ("representation for& previously given#",
8332 Set_Enumeration_Rep_Expr
(Elit
, Expression
(Assoc
));
8334 Expr
:= Expression
(Assoc
);
8335 Val
:= Static_Integer
(Expr
);
8340 elsif Val
< Lo
or else Hi
< Val
then
8341 Error_Msg_N
("value outside permitted range", Expr
);
8345 Set_Enumeration_Rep
(Elit
, Val
);
8356 -- Aggregate is fully processed. Now we check that a full set of
8357 -- representations was given, and that they are in range and in order.
8358 -- These checks are only done if no other errors occurred.
8364 Elit
:= First_Literal
(Enumtype
);
8365 while Present
(Elit
) loop
8366 if No
(Enumeration_Rep_Expr
(Elit
)) then
8367 Error_Msg_NE
("missing representation for&!", N
, Elit
);
8370 Val
:= Enumeration_Rep
(Elit
);
8376 if Present
(Val
) then
8377 if Present
(Max
) and then Val
<= Max
then
8379 ("enumeration value for& not ordered!",
8380 Enumeration_Rep_Expr
(Elit
), Elit
);
8383 Max_Node
:= Enumeration_Rep_Expr
(Elit
);
8387 -- If there is at least one literal whose representation is not
8388 -- equal to the Pos value, then note that this enumeration type
8389 -- has a non-standard representation.
8391 if Val
/= Enumeration_Pos
(Elit
) then
8392 Set_Has_Non_Standard_Rep
(Base_Type
(Enumtype
));
8399 -- Now set proper size information
8402 Minsize
: Uint
:= UI_From_Int
(Minimum_Size
(Enumtype
));
8405 if Has_Size_Clause
(Enumtype
) then
8407 -- All OK, if size is OK now
8409 if RM_Size
(Enumtype
) >= Minsize
then
8413 -- Try if we can get by with biasing
8416 UI_From_Int
(Minimum_Size
(Enumtype
, Biased
=> True));
8418 -- Error message if even biasing does not work
8420 if RM_Size
(Enumtype
) < Minsize
then
8421 Error_Msg_Uint_1
:= RM_Size
(Enumtype
);
8422 Error_Msg_Uint_2
:= Max
;
8424 ("previously given size (^) is too small "
8425 & "for this value (^)", Max_Node
);
8427 -- If biasing worked, indicate that we now have biased rep
8431 (Enumtype
, Size_Clause
(Enumtype
), "size clause");
8436 Set_RM_Size
(Enumtype
, Minsize
);
8437 Set_Enum_Esize
(Enumtype
);
8440 Set_RM_Size
(Base_Type
(Enumtype
), RM_Size
(Enumtype
));
8441 Set_Esize
(Base_Type
(Enumtype
), Esize
(Enumtype
));
8443 Copy_Alignment
(To
=> Base_Type
(Enumtype
), From
=> Enumtype
);
8447 -- We repeat the too late test in case it froze itself
8449 if Rep_Item_Too_Late
(Enumtype
, N
) then
8452 end Analyze_Enumeration_Representation_Clause
;
8454 ----------------------------
8455 -- Analyze_Free_Statement --
8456 ----------------------------
8458 procedure Analyze_Free_Statement
(N
: Node_Id
) is
8460 Analyze
(Expression
(N
));
8461 end Analyze_Free_Statement
;
8463 ---------------------------
8464 -- Analyze_Freeze_Entity --
8465 ---------------------------
8467 procedure Analyze_Freeze_Entity
(N
: Node_Id
) is
8469 Freeze_Entity_Checks
(N
);
8470 end Analyze_Freeze_Entity
;
8472 -----------------------------------
8473 -- Analyze_Freeze_Generic_Entity --
8474 -----------------------------------
8476 procedure Analyze_Freeze_Generic_Entity
(N
: Node_Id
) is
8477 E
: constant Entity_Id
:= Entity
(N
);
8480 if not Is_Frozen
(E
) and then Has_Delayed_Aspects
(E
) then
8481 Analyze_Aspects_At_Freeze_Point
(E
);
8484 Freeze_Entity_Checks
(N
);
8485 end Analyze_Freeze_Generic_Entity
;
8487 ------------------------------------------
8488 -- Analyze_Record_Representation_Clause --
8489 ------------------------------------------
8491 -- Note: we check as much as we can here, but we can't do any checks
8492 -- based on the position values (e.g. overlap checks) until freeze time
8493 -- because especially in Ada 2005 (machine scalar mode), the processing
8494 -- for non-standard bit order can substantially change the positions.
8495 -- See procedure Check_Record_Representation_Clause (called from Freeze)
8496 -- for the remainder of this processing.
8498 procedure Analyze_Record_Representation_Clause
(N
: Node_Id
) is
8499 Ident
: constant Node_Id
:= Identifier
(N
);
8507 Rectype
: Entity_Id
;
8510 function Is_Inherited
(Comp
: Entity_Id
) return Boolean;
8511 -- True if Comp is an inherited component in a record extension
8517 function Is_Inherited
(Comp
: Entity_Id
) return Boolean is
8518 Comp_Base
: Entity_Id
;
8521 if Ekind
(Rectype
) = E_Record_Subtype
then
8522 Comp_Base
:= Original_Record_Component
(Comp
);
8527 return Comp_Base
/= Original_Record_Component
(Comp_Base
);
8532 Is_Record_Extension
: Boolean;
8533 -- True if Rectype is a record extension
8535 CR_Pragma
: Node_Id
:= Empty
;
8536 -- Points to N_Pragma node if Complete_Representation pragma present
8538 -- Start of processing for Analyze_Record_Representation_Clause
8541 if Ignore_Rep_Clauses
then
8542 Kill_Rep_Clause
(N
);
8547 Rectype
:= Entity
(Ident
);
8549 if Rectype
= Any_Type
or else Rep_Item_Too_Early
(Rectype
, N
) then
8552 Rectype
:= Underlying_Type
(Rectype
);
8555 -- First some basic error checks
8557 if not Is_Record_Type
(Rectype
) then
8559 ("record type required, found}", Ident
, First_Subtype
(Rectype
));
8562 elsif Scope
(Rectype
) /= Current_Scope
then
8563 Error_Msg_N
("type must be declared in this scope", N
);
8566 elsif not Is_First_Subtype
(Rectype
) then
8567 Error_Msg_N
("cannot give record rep clause for subtype", N
);
8570 elsif Has_Record_Rep_Clause
(Rectype
) then
8571 Error_Msg_N
("duplicate record rep clause ignored", N
);
8574 elsif Rep_Item_Too_Late
(Rectype
, N
) then
8578 -- We know we have a first subtype, now possibly go to the anonymous
8579 -- base type to determine whether Rectype is a record extension.
8581 Recdef
:= Type_Definition
(Declaration_Node
(Base_Type
(Rectype
)));
8582 Is_Record_Extension
:=
8583 Nkind
(Recdef
) = N_Derived_Type_Definition
8584 and then Present
(Record_Extension_Part
(Recdef
));
8586 if Present
(Mod_Clause
(N
)) then
8588 M
: constant Node_Id
:= Mod_Clause
(N
);
8589 P
: constant List_Id
:= Pragmas_Before
(M
);
8593 Check_Restriction
(No_Obsolescent_Features
, Mod_Clause
(N
));
8595 if Warn_On_Obsolescent_Feature
then
8597 ("?j?mod clause is an obsolescent feature (RM J.8)", N
);
8599 ("\?j?use alignment attribute definition clause instead", N
);
8606 -- Get the alignment value to perform error checking
8608 Ignore
:= Get_Alignment_Value
(Expression
(M
));
8612 -- For untagged types, clear any existing component clauses for the
8613 -- type. If the type is derived, this is what allows us to override
8614 -- a rep clause for the parent. For type extensions, the representation
8615 -- of the inherited components is inherited, so we want to keep previous
8616 -- component clauses for completeness.
8618 if not Is_Tagged_Type
(Rectype
) then
8619 Comp
:= First_Component_Or_Discriminant
(Rectype
);
8620 while Present
(Comp
) loop
8621 Set_Component_Clause
(Comp
, Empty
);
8622 Next_Component_Or_Discriminant
(Comp
);
8626 -- All done if no component clauses
8628 CC
:= First
(Component_Clauses
(N
));
8634 -- A representation like this applies to the base type
8636 Set_Has_Record_Rep_Clause
(Base_Type
(Rectype
));
8637 Set_Has_Non_Standard_Rep
(Base_Type
(Rectype
));
8638 Set_Has_Specified_Layout
(Base_Type
(Rectype
));
8640 -- Process the component clauses
8642 while Present
(CC
) loop
8646 if Nkind
(CC
) = N_Pragma
then
8649 -- The only pragma of interest is Complete_Representation
8651 if Pragma_Name
(CC
) = Name_Complete_Representation
then
8655 -- Processing for real component clause
8658 Posit
:= Static_Integer
(Position
(CC
));
8659 Fbit
:= Static_Integer
(First_Bit
(CC
));
8660 Lbit
:= Static_Integer
(Last_Bit
(CC
));
8663 and then Present
(Fbit
)
8664 and then Present
(Lbit
)
8667 Error_Msg_N
("position cannot be negative", Position
(CC
));
8670 Error_Msg_N
("first bit cannot be negative", First_Bit
(CC
));
8672 -- The Last_Bit specified in a component clause must not be
8673 -- less than the First_Bit minus one (RM-13.5.1(10)).
8675 elsif Lbit
< Fbit
- 1 then
8677 ("last bit cannot be less than first bit minus one",
8680 -- Values look OK, so find the corresponding record component
8681 -- Even though the syntax allows an attribute reference for
8682 -- implementation-defined components, GNAT does not allow the
8683 -- tag to get an explicit position.
8685 elsif Nkind
(Component_Name
(CC
)) = N_Attribute_Reference
then
8686 if Attribute_Name
(Component_Name
(CC
)) = Name_Tag
then
8687 Error_Msg_N
("position of tag cannot be specified", CC
);
8689 Error_Msg_N
("illegal component name", CC
);
8693 Comp
:= First_Entity
(Rectype
);
8694 while Present
(Comp
) loop
8695 exit when Chars
(Comp
) = Chars
(Component_Name
(CC
));
8701 -- Maybe component of base type that is absent from
8702 -- statically constrained first subtype.
8704 Comp
:= First_Entity
(Base_Type
(Rectype
));
8705 while Present
(Comp
) loop
8706 exit when Chars
(Comp
) = Chars
(Component_Name
(CC
));
8713 ("component clause is for non-existent field", CC
);
8715 -- Ada 2012 (AI05-0026): Any name that denotes a
8716 -- discriminant of an object of an unchecked union type
8717 -- shall not occur within a record_representation_clause.
8719 -- The general restriction of using record rep clauses on
8720 -- Unchecked_Union types has now been lifted. Since it is
8721 -- possible to introduce a record rep clause which mentions
8722 -- the discriminant of an Unchecked_Union in non-Ada 2012
8723 -- code, this check is applied to all versions of the
8726 elsif Ekind
(Comp
) = E_Discriminant
8727 and then Is_Unchecked_Union
(Rectype
)
8730 ("cannot reference discriminant of unchecked union",
8731 Component_Name
(CC
));
8733 elsif Is_Record_Extension
and then Is_Inherited
(Comp
) then
8735 ("component clause not allowed for inherited "
8736 & "component&", CC
, Comp
);
8738 elsif Present
(Component_Clause
(Comp
)) then
8740 -- Diagnose duplicate rep clause, or check consistency
8741 -- if this is an inherited component. In a double fault,
8742 -- there may be a duplicate inconsistent clause for an
8743 -- inherited component.
8745 if Scope
(Original_Record_Component
(Comp
)) = Rectype
8746 or else Parent
(Component_Clause
(Comp
)) = N
8748 Error_Msg_Sloc
:= Sloc
(Component_Clause
(Comp
));
8749 Error_Msg_N
("component clause previously given#", CC
);
8753 Rep1
: constant Node_Id
:= Component_Clause
(Comp
);
8755 if Intval
(Position
(Rep1
)) /=
8756 Intval
(Position
(CC
))
8757 or else Intval
(First_Bit
(Rep1
)) /=
8758 Intval
(First_Bit
(CC
))
8759 or else Intval
(Last_Bit
(Rep1
)) /=
8760 Intval
(Last_Bit
(CC
))
8763 ("component clause inconsistent with "
8764 & "representation of ancestor", CC
);
8766 elsif Warn_On_Redundant_Constructs
then
8768 ("?r?redundant confirming component clause "
8769 & "for component!", CC
);
8774 -- Normal case where this is the first component clause we
8775 -- have seen for this entity, so set it up properly.
8778 -- Make reference for field in record rep clause and set
8779 -- appropriate entity field in the field identifier.
8782 (Comp
, Component_Name
(CC
), Set_Ref
=> False);
8783 Set_Entity_With_Checks
(Component_Name
(CC
), Comp
);
8785 -- Update Fbit and Lbit to the actual bit number
8787 Fbit
:= Fbit
+ UI_From_Int
(SSU
) * Posit
;
8788 Lbit
:= Lbit
+ UI_From_Int
(SSU
) * Posit
;
8790 if Has_Size_Clause
(Rectype
)
8791 and then RM_Size
(Rectype
) <= Lbit
8793 Error_Msg_Uint_1
:= RM_Size
(Rectype
);
8794 Error_Msg_Uint_2
:= Lbit
+ 1;
8795 Error_Msg_N
("bit number out of range of specified "
8796 & "size (expected ^, got ^)",
8799 Set_Component_Clause
(Comp
, CC
);
8800 Set_Component_Bit_Offset
(Comp
, Fbit
);
8801 Set_Esize
(Comp
, 1 + (Lbit
- Fbit
));
8802 Set_Normalized_First_Bit
(Comp
, Fbit
mod SSU
);
8803 Set_Normalized_Position
(Comp
, Fbit
/ SSU
);
8805 if Warn_On_Overridden_Size
8806 and then Has_Size_Clause
(Etype
(Comp
))
8807 and then RM_Size
(Etype
(Comp
)) /= Esize
(Comp
)
8810 ("?.s?component size overrides size clause for&",
8811 Component_Name
(CC
), Etype
(Comp
));
8815 (Component_Name
(CC
),
8821 (Comp
, First_Node
(CC
), "component clause", Biased
);
8823 -- This information is also set in the corresponding
8824 -- component of the base type, found by accessing the
8825 -- Original_Record_Component link if it is present.
8827 Ocomp
:= Original_Record_Component
(Comp
);
8829 if Present
(Ocomp
) and then Ocomp
/= Comp
then
8830 Set_Component_Clause
(Ocomp
, CC
);
8831 Set_Component_Bit_Offset
(Ocomp
, Fbit
);
8832 Set_Esize
(Ocomp
, 1 + (Lbit
- Fbit
));
8833 Set_Normalized_First_Bit
(Ocomp
, Fbit
mod SSU
);
8834 Set_Normalized_Position
(Ocomp
, Fbit
/ SSU
);
8836 -- Note: we don't use Set_Biased here, because we
8837 -- already gave a warning above if needed, and we
8838 -- would get a duplicate for the same name here.
8840 Set_Has_Biased_Representation
8841 (Ocomp
, Has_Biased_Representation
(Comp
));
8844 if Esize
(Comp
) < 0 then
8845 Error_Msg_N
("component size is negative", CC
);
8856 -- Check missing components if Complete_Representation pragma appeared
8858 if Present
(CR_Pragma
) then
8859 Comp
:= First_Component_Or_Discriminant
(Rectype
);
8860 while Present
(Comp
) loop
8861 if No
(Component_Clause
(Comp
)) then
8863 ("missing component clause for &", CR_Pragma
, Comp
);
8866 Next_Component_Or_Discriminant
(Comp
);
8869 -- Give missing components warning if required
8871 elsif Warn_On_Unrepped_Components
then
8873 Num_Repped_Components
: Nat
:= 0;
8874 Num_Unrepped_Components
: Nat
:= 0;
8877 -- First count number of repped and unrepped components
8879 Comp
:= First_Component_Or_Discriminant
(Rectype
);
8880 while Present
(Comp
) loop
8881 if Present
(Component_Clause
(Comp
)) then
8882 Num_Repped_Components
:= Num_Repped_Components
+ 1;
8884 Num_Unrepped_Components
:= Num_Unrepped_Components
+ 1;
8887 Next_Component_Or_Discriminant
(Comp
);
8890 -- We are only interested in the case where there is at least one
8891 -- unrepped component, and at least half the components have rep
8892 -- clauses. We figure that if less than half have them, then the
8893 -- partial rep clause is really intentional. If the component
8894 -- type has no underlying type set at this point (as for a generic
8895 -- formal type), we don't know enough to give a warning on the
8898 if Num_Unrepped_Components
> 0
8899 and then Num_Unrepped_Components
< Num_Repped_Components
8901 Comp
:= First_Component_Or_Discriminant
(Rectype
);
8902 while Present
(Comp
) loop
8903 if No
(Component_Clause
(Comp
))
8904 and then Comes_From_Source
(Comp
)
8905 and then Present
(Underlying_Type
(Etype
(Comp
)))
8906 and then (Is_Scalar_Type
(Underlying_Type
(Etype
(Comp
)))
8907 or else Size_Known_At_Compile_Time
8908 (Underlying_Type
(Etype
(Comp
))))
8909 and then not Has_Warnings_Off
(Rectype
)
8911 -- Ignore discriminant in unchecked union, since it is
8912 -- not there, and cannot have a component clause.
8914 and then (not Is_Unchecked_Union
(Rectype
)
8915 or else Ekind
(Comp
) /= E_Discriminant
)
8917 Error_Msg_Sloc
:= Sloc
(Comp
);
8919 ("?.c?no component clause given for & declared #",
8923 Next_Component_Or_Discriminant
(Comp
);
8928 end Analyze_Record_Representation_Clause
;
8930 ----------------------------------------------
8931 -- Analyze_User_Aspect_Aspect_Specification --
8932 ----------------------------------------------
8934 procedure Analyze_User_Aspect_Aspect_Specification
(N
: Node_Id
) is
8935 OK
: Boolean := True;
8937 procedure Analyze_One_User_Aspect
(Id
: Node_Id
);
8938 -- A User_Aspect aspect specification may specify multiple
8939 -- user-defined aspects. This procedure is called for each one.
8941 -----------------------------
8942 -- Analyze_One_User_Aspect --
8943 -----------------------------
8945 procedure Analyze_One_User_Aspect
(Id
: Node_Id
) is
8946 UAD_Pragma
: constant Node_Id
:=
8947 User_Aspect_Support
.Registered_UAD_Pragma
(Chars
(Id
));
8951 if No
(UAD_Pragma
) then
8952 Error_Msg_N
("No definition for user-defined aspect", Id
);
8956 -- Process args in reverse order so that inserted
8957 -- aspect specs end up in "right" order (although
8958 -- order shouldn't matter).
8959 Arg
:= Last
(Pragma_Argument_Associations
(UAD_Pragma
));
8961 -- Skip first argument, which is the name of the
8962 -- user-defined aspect.
8963 while Present
(Prev
(Arg
)) loop
8965 Exp
: constant Node_Id
:= Expression
(Arg
);
8966 New_Sloc
: constant Source_Ptr
:= Sloc
(N
);
8967 New_Aspect_Spec
: Node_Id
;
8969 New_Exp_List
: List_Id
;
8972 when N_Identifier
=>
8974 Make_Aspect_Specification
8977 New_Copy_Tree
(Exp
, New_Sloc
=> New_Sloc
));
8979 when N_Indexed_Component
=>
8980 New_Exp_List
:= New_List
;
8983 Index_Exp
: Node_Id
:= First
(Expressions
(Exp
));
8985 while Present
(Index_Exp
) loop
8986 Append
(New_Copy_Tree
8987 (Index_Exp
, New_Sloc
=> New_Sloc
),
8988 To
=> New_Exp_List
);
8993 New_Exp
:= Make_Aggregate
8995 Expressions
=> New_Exp_List
,
8996 Is_Parenthesis_Aggregate
=> True);
8999 Make_Aspect_Specification
9002 New_Copy_Tree
(Prefix
(Exp
), New_Sloc
=> New_Sloc
),
9003 Expression
=> New_Exp
);
9006 raise Program_Error
;
9009 Insert_After
(After
=> N
, Node
=> New_Aspect_Spec
);
9013 end Analyze_One_User_Aspect
;
9015 if Analyzed
(N
) then
9019 -- This aspect can be specified for any entity whose
9020 -- syntax allows an aspect specification.
9021 -- The analysis code below constructs new aspect
9022 -- specifications for the given entity; each might
9023 -- turn out to be legal or illegal. That is determined
9024 -- when each of these new aspect_specs is analyzed.
9026 case Nkind
(Expression
(N
)) is
9027 when N_Identifier
=>
9028 Analyze_One_User_Aspect
(Expression
(N
));
9030 OK
:= Is_Parenthesis_Aggregate
(Expression
(N
));
9032 Id
: Node_Id
:= First
(Expressions
(Expression
(N
)));
9034 while Present
(Id
) loop
9035 if Nkind
(Id
) = N_Identifier
then
9036 Analyze_One_User_Aspect
(Id
);
9049 ("Bad argument for User_Aspect aspect specification", N
);
9053 end Analyze_User_Aspect_Aspect_Specification
;
9055 -------------------------------------
9056 -- Build_Discrete_Static_Predicate --
9057 -------------------------------------
9059 procedure Build_Discrete_Static_Predicate
9064 Loc
: constant Source_Ptr
:= Sloc
(Expr
);
9066 Btyp
: constant Entity_Id
:= Base_Type
(Typ
);
9068 BLo
: constant Uint
:= Expr_Value
(Type_Low_Bound
(Btyp
));
9069 BHi
: constant Uint
:= Expr_Value
(Type_High_Bound
(Btyp
));
9070 -- Low bound and high bound value of base type of Typ
9074 -- Bounds for constructing the static predicate. We use the bound of the
9075 -- subtype if it is static, otherwise the corresponding base type bound.
9076 -- Note: a non-static subtype can have a static predicate.
9081 -- One entry in a Rlist value, a single REnt (range entry) value denotes
9082 -- one range from Lo to Hi. To represent a single value range Lo = Hi =
9085 type RList
is array (Nat
range <>) of REnt
;
9086 -- A list of ranges. The ranges are sorted in increasing order, and are
9087 -- disjoint (there is a gap of at least one value between each range in
9088 -- the table). A value is in the set of ranges in Rlist if it lies
9089 -- within one of these ranges.
9091 False_Range
: constant RList
:=
9092 RList
'(1 .. 0 => REnt'(No_Uint
, No_Uint
));
9093 -- An empty set of ranges represents a range list that can never be
9094 -- satisfied, since there are no ranges in which the value could lie,
9095 -- so it does not lie in any of them. False_Range is a canonical value
9096 -- for this empty set, but general processing should test for an Rlist
9097 -- with length zero (see Is_False predicate), since other null ranges
9098 -- may appear which must be treated as False.
9100 True_Range
: constant RList
:= RList
'(1 => REnt'(BLo
, BHi
));
9101 -- Range representing True, value must be in the base range
9103 function "and" (Left
: RList
; Right
: RList
) return RList
;
9104 -- And's together two range lists, returning a range list. This is a set
9105 -- intersection operation.
9107 function "or" (Left
: RList
; Right
: RList
) return RList
;
9108 -- Or's together two range lists, returning a range list. This is a set
9111 function "not" (Right
: RList
) return RList
;
9112 -- Returns complement of a given range list, i.e. a range list
9113 -- representing all the values in TLo .. THi that are not in the input
9116 function Build_Val
(V
: Uint
) return Node_Id
;
9117 -- Return an analyzed N_Identifier node referencing this value, suitable
9118 -- for use as an entry in the Static_Discrete_Predicate list. This node
9119 -- is typed with the base type.
9121 function Build_Range
(Lo
: Uint
; Hi
: Uint
) return Node_Id
;
9122 -- Return an analyzed N_Range node referencing this range, suitable for
9123 -- use as an entry in the Static_Discrete_Predicate list. This node is
9124 -- typed with the base type.
9128 Static
: access Boolean) return RList
;
9129 -- This is a recursive routine that converts the given expression into a
9130 -- list of ranges, suitable for use in building the static predicate.
9131 -- Static.all will be set to False if the expression is found to be non
9132 -- static. Note that Static.all should be set to True by the caller.
9134 function Is_False
(R
: RList
) return Boolean;
9135 pragma Inline
(Is_False
);
9136 -- Returns True if the given range list is empty, and thus represents a
9137 -- False list of ranges that can never be satisfied.
9139 function Is_True
(R
: RList
) return Boolean;
9140 -- Returns True if R trivially represents the True predicate by having a
9141 -- single range from BLo to BHi.
9143 function Is_Type_Ref
(N
: Node_Id
) return Boolean;
9144 pragma Inline
(Is_Type_Ref
);
9145 -- Returns if True if N is a reference to the type for the predicate in
9146 -- the expression (i.e. if it is an identifier whose Chars field matches
9147 -- the Nam given in the call). N must not be parenthesized, if the type
9148 -- name appears in parens, this routine will return False.
9150 function Lo_Val
(N
: Node_Id
) return Uint
;
9151 -- Given an entry from a Static_Discrete_Predicate list that is either
9152 -- a static expression or static range, gets either the expression value
9153 -- or the low bound of the range.
9155 function Hi_Val
(N
: Node_Id
) return Uint
;
9156 -- Given an entry from a Static_Discrete_Predicate list that is either
9157 -- a static expression or static range, gets either the expression value
9158 -- or the high bound of the range.
9160 function Membership_Entry
9161 (N
: Node_Id
; Static
: access Boolean) return RList
;
9162 -- Given a single membership entry (range, value, or subtype), returns
9163 -- the corresponding range list. Set Static.all to False if not static.
9165 function Membership_Entries
9166 (N
: Node_Id
; Static
: access Boolean) return RList
;
9167 -- Given an element on an alternatives list of a membership operation,
9168 -- returns the range list corresponding to this entry and all following
9169 -- entries (i.e. returns the "or" of this list of values).
9170 -- Set Static.all to False if not static.
9174 Static
: access Boolean) return RList
;
9175 -- Given a type, if it has a static predicate, then set Result to the
9176 -- predicate as a range list, otherwise set Static.all to False.
9178 procedure Warn_If_Test_Ineffective
(REntry
: REnt
; N
: Node_Id
);
9179 -- Issue a warning if REntry includes only values that are
9180 -- outside the range TLo .. THi.
9186 function "and" (Left
: RList
; Right
: RList
) return RList
is
9188 -- First range of result
9190 SLeft
: Nat
:= Left
'First;
9191 -- Start of rest of left entries
9193 SRight
: Nat
:= Right
'First;
9194 -- Start of rest of right entries
9197 -- If either range is True, return the other
9199 if Is_True
(Left
) then
9201 elsif Is_True
(Right
) then
9205 -- If either range is False, return False
9207 if Is_False
(Left
) or else Is_False
(Right
) then
9211 -- Loop to remove entries at start that are disjoint, and thus just
9212 -- get discarded from the result entirely.
9215 -- If no operands left in either operand, result is false
9217 if SLeft
> Left
'Last or else SRight
> Right
'Last then
9220 -- Discard first left operand entry if disjoint with right
9222 elsif Left
(SLeft
).Hi
< Right
(SRight
).Lo
then
9225 -- Discard first right operand entry if disjoint with left
9227 elsif Right
(SRight
).Hi
< Left
(SLeft
).Lo
then
9228 SRight
:= SRight
+ 1;
9230 -- Otherwise we have an overlapping entry
9237 -- Now we have two non-null operands, and first entries overlap. The
9238 -- first entry in the result will be the overlapping part of these
9241 FEnt
:= REnt
'(Lo => UI_Max (Left (SLeft).Lo, Right (SRight).Lo),
9242 Hi => UI_Min (Left (SLeft).Hi, Right (SRight).Hi));
9244 -- Now we can remove the entry that ended at a lower value, since its
9245 -- contribution is entirely contained in Fent.
9247 if Left (SLeft).Hi <= Right (SRight).Hi then
9250 SRight := SRight + 1;
9253 -- Compute result by concatenating this first entry with the "and" of
9254 -- the remaining parts of the left and right operands. Note that if
9255 -- either of these is empty, "and" will yield empty, so that we will
9256 -- end up with just Fent, which is what we want in that case.
9259 FEnt & (Left (SLeft .. Left'Last) and Right (SRight .. Right'Last));
9266 function "not" (Right : RList) return RList is
9268 -- Return True if False range
9270 if Is_False (Right) then
9274 -- Return False if True range
9276 if Is_True (Right) then
9280 -- Here if not trivial case
9283 Result : RList (1 .. Right'Length + 1);
9284 -- May need one more entry for gap at beginning and end
9287 -- Number of entries stored in Result
9292 if Right (Right'First).Lo > TLo then
9294 Result (Count) := REnt'(TLo
, Right
(Right
'First).Lo
- 1);
9297 -- Gaps between ranges
9299 for J
in Right
'First .. Right
'Last - 1 loop
9301 Result
(Count
) := REnt
'(Right (J).Hi + 1, Right (J + 1).Lo - 1);
9306 if Right (Right'Last).Hi < THi then
9308 Result (Count) := REnt'(Right
(Right
'Last).Hi
+ 1, THi
);
9311 return Result
(1 .. Count
);
9319 function "or" (Left
: RList
; Right
: RList
) return RList
is
9321 -- First range of result
9323 SLeft
: Nat
:= Left
'First;
9324 -- Start of rest of left entries
9326 SRight
: Nat
:= Right
'First;
9327 -- Start of rest of right entries
9330 -- If either range is True, return True
9332 if Is_True
(Left
) or else Is_True
(Right
) then
9336 -- If either range is False (empty), return the other
9338 if Is_False
(Left
) then
9340 elsif Is_False
(Right
) then
9344 -- Initialize result first entry from left or right operand depending
9345 -- on which starts with the lower range.
9347 if Left
(SLeft
).Lo
< Right
(SRight
).Lo
then
9348 FEnt
:= Left
(SLeft
);
9351 FEnt
:= Right
(SRight
);
9352 SRight
:= SRight
+ 1;
9355 -- This loop eats ranges from left and right operands that are
9356 -- contiguous with the first range we are gathering.
9359 -- Eat first entry in left operand if contiguous or overlapped by
9360 -- gathered first operand of result.
9362 if SLeft
<= Left
'Last
9363 and then Left
(SLeft
).Lo
<= FEnt
.Hi
+ 1
9365 FEnt
.Hi
:= UI_Max
(FEnt
.Hi
, Left
(SLeft
).Hi
);
9368 -- Eat first entry in right operand if contiguous or overlapped by
9369 -- gathered right operand of result.
9371 elsif SRight
<= Right
'Last
9372 and then Right
(SRight
).Lo
<= FEnt
.Hi
+ 1
9374 FEnt
.Hi
:= UI_Max
(FEnt
.Hi
, Right
(SRight
).Hi
);
9375 SRight
:= SRight
+ 1;
9377 -- All done if no more entries to eat
9384 -- Obtain result as the first entry we just computed, concatenated
9385 -- to the "or" of the remaining results (if one operand is empty,
9386 -- this will just concatenate with the other
9389 FEnt
& (Left
(SLeft
.. Left
'Last) or Right
(SRight
.. Right
'Last));
9396 function Build_Range
(Lo
: Uint
; Hi
: Uint
) return Node_Id
is
9401 Low_Bound
=> Build_Val
(Lo
),
9402 High_Bound
=> Build_Val
(Hi
));
9403 Set_Etype
(Result
, Btyp
);
9404 Set_Analyzed
(Result
);
9412 function Build_Val
(V
: Uint
) return Node_Id
is
9416 if Is_Enumeration_Type
(Typ
) then
9417 Result
:= Get_Enum_Lit_From_Pos
(Typ
, V
, Loc
);
9419 Result
:= Make_Integer_Literal
(Loc
, V
);
9422 Set_Etype
(Result
, Btyp
);
9423 Set_Is_Static_Expression
(Result
);
9424 Set_Analyzed
(Result
);
9434 Static
: access Boolean) return RList
9438 Val_Bearer
: Node_Id
;
9441 -- Static expression can only be true or false
9443 if Is_OK_Static_Expression
(Exp
) then
9444 if Expr_Value
(Exp
) = 0 then
9451 -- Otherwise test node type
9462 return Get_RList
(Left_Opnd
(Exp
), Static
)
9464 Get_RList
(Right_Opnd
(Exp
), Static
);
9471 return Get_RList
(Left_Opnd
(Exp
), Static
)
9473 Get_RList
(Right_Opnd
(Exp
), Static
);
9478 return not Get_RList
(Right_Opnd
(Exp
), Static
);
9480 -- Comparisons of type with static value
9482 when N_Op_Compare
=>
9484 -- Type is left operand
9486 if Is_Type_Ref
(Left_Opnd
(Exp
))
9487 and then Is_OK_Static_Expression
(Right_Opnd
(Exp
))
9489 Val_Bearer
:= Right_Opnd
(Exp
);
9491 -- Typ is right operand
9493 elsif Is_Type_Ref
(Right_Opnd
(Exp
))
9494 and then Is_OK_Static_Expression
(Left_Opnd
(Exp
))
9496 Val_Bearer
:= Left_Opnd
(Exp
);
9498 -- Invert sense of comparison
9501 when N_Op_Gt
=> Op
:= N_Op_Lt
;
9502 when N_Op_Lt
=> Op
:= N_Op_Gt
;
9503 when N_Op_Ge
=> Op
:= N_Op_Le
;
9504 when N_Op_Le
=> Op
:= N_Op_Ge
;
9505 when others => null;
9508 -- Other cases are non-static
9511 Static
.all := False;
9515 Val
:= Expr_Value
(Val_Bearer
);
9517 -- Construct range according to comparison operation
9524 REntry
:= (Val
, Val
);
9527 REntry
:= (Val
, THi
);
9530 REntry
:= (Val
+ 1, THi
);
9533 REntry
:= (TLo
, Val
);
9536 REntry
:= (TLo
, Val
- 1);
9539 Warn_If_Test_Ineffective
((Val
, Val
), Val_Bearer
);
9540 return RList
'(REnt'(TLo
, Val
- 1),
9541 REnt
'(Val + 1, THi));
9544 raise Program_Error;
9547 Warn_If_Test_Ineffective (REntry, Val_Bearer);
9548 return RList'(1 => REntry
);
9554 if not Is_Type_Ref
(Left_Opnd
(Exp
)) then
9555 Static
.all := False;
9559 if Present
(Right_Opnd
(Exp
)) then
9560 return Membership_Entry
(Right_Opnd
(Exp
), Static
);
9562 return Membership_Entries
9563 (First
(Alternatives
(Exp
)), Static
);
9566 -- Negative membership (NOT IN)
9569 if not Is_Type_Ref
(Left_Opnd
(Exp
)) then
9570 Static
.all := False;
9574 if Present
(Right_Opnd
(Exp
)) then
9575 return not Membership_Entry
(Right_Opnd
(Exp
), Static
);
9577 return not Membership_Entries
9578 (First
(Alternatives
(Exp
)), Static
);
9581 -- Function call, may be call to static predicate
9583 when N_Function_Call
=>
9584 if Is_Entity_Name
(Name
(Exp
)) then
9586 Ent
: constant Entity_Id
:= Entity
(Name
(Exp
));
9588 if Is_Predicate_Function
(Ent
) then
9589 return Stat_Pred
(Etype
(First_Formal
(Ent
)), Static
);
9594 -- Other function call cases are non-static
9596 Static
.all := False;
9599 -- Qualified expression, dig out the expression
9601 when N_Qualified_Expression
=>
9602 return Get_RList
(Expression
(Exp
), Static
);
9604 when N_Case_Expression
=>
9611 if not Is_Entity_Name
(Expression
(Expr
))
9612 or else Etype
(Expression
(Expr
)) /= Typ
9615 ("expression must denote subtype", Expression
(Expr
));
9619 -- Collect discrete choices in all True alternatives
9621 Choices
:= New_List
;
9622 Alt
:= First
(Alternatives
(Exp
));
9623 while Present
(Alt
) loop
9624 Dep
:= Expression
(Alt
);
9626 if not Is_OK_Static_Expression
(Dep
) then
9627 Static
.all := False;
9630 elsif Is_True
(Expr_Value
(Dep
)) then
9631 Append_List_To
(Choices
,
9632 New_Copy_List
(Discrete_Choices
(Alt
)));
9638 return Membership_Entries
(First
(Choices
), Static
);
9641 -- Expression with actions: if no actions, dig out expression
9643 when N_Expression_With_Actions
=>
9644 if Is_Empty_List
(Actions
(Exp
)) then
9645 return Get_RList
(Expression
(Exp
), Static
);
9647 Static
.all := False;
9654 return (Get_RList
(Left_Opnd
(Exp
), Static
)
9655 and not Get_RList
(Right_Opnd
(Exp
), Static
))
9656 or (Get_RList
(Right_Opnd
(Exp
), Static
)
9657 and not Get_RList
(Left_Opnd
(Exp
), Static
));
9659 -- Any other node type is non-static
9662 Static
.all := False;
9671 function Hi_Val
(N
: Node_Id
) return Uint
is
9673 if Is_OK_Static_Expression
(N
) then
9674 return Expr_Value
(N
);
9676 pragma Assert
(Nkind
(N
) = N_Range
);
9677 return Expr_Value
(High_Bound
(N
));
9685 function Is_False
(R
: RList
) return Boolean is
9687 return R
'Length = 0;
9694 function Is_True
(R
: RList
) return Boolean is
9697 and then R
(R
'First).Lo
= BLo
9698 and then R
(R
'First).Hi
= BHi
;
9705 function Is_Type_Ref
(N
: Node_Id
) return Boolean is
9707 return Nkind
(N
) = N_Identifier
9708 and then Chars
(N
) = Nam
9709 and then Paren_Count
(N
) = 0;
9716 function Lo_Val
(N
: Node_Id
) return Uint
is
9718 if Is_OK_Static_Expression
(N
) then
9719 return Expr_Value
(N
);
9721 pragma Assert
(Nkind
(N
) = N_Range
);
9722 return Expr_Value
(Low_Bound
(N
));
9726 ------------------------
9727 -- Membership_Entries --
9728 ------------------------
9730 function Membership_Entries
9731 (N
: Node_Id
; Static
: access Boolean) return RList
is
9733 if No
(Next
(N
)) then
9734 return Membership_Entry
(N
, Static
);
9736 return Membership_Entry
(N
, Static
)
9737 or Membership_Entries
(Next
(N
), Static
);
9739 end Membership_Entries
;
9741 ----------------------
9742 -- Membership_Entry --
9743 ----------------------
9745 function Membership_Entry
9746 (N
: Node_Id
; Static
: access Boolean) return RList
9755 if Nkind
(N
) = N_Range
then
9756 if not Is_OK_Static_Expression
(Low_Bound
(N
))
9758 not Is_OK_Static_Expression
(High_Bound
(N
))
9760 Static
.all := False;
9763 SLo
:= Expr_Value
(Low_Bound
(N
));
9764 SHi
:= Expr_Value
(High_Bound
(N
));
9766 REntry
: constant REnt
:= (SLo
, SHi
);
9768 Warn_If_Test_Ineffective
(REntry
, N
);
9769 return RList
'(1 => REntry);
9775 elsif Nkind (N) = N_Others_Choice then
9777 Choices : constant List_Id := Others_Discrete_Choices (N);
9779 Range_List : RList (1 .. List_Length (Choices));
9782 Choice := First (Choices);
9784 for J in Range_List'Range loop
9785 Range_List (J) := REnt'(Lo_Val
(Choice
), Hi_Val
(Choice
));
9792 -- Static expression case
9794 elsif Is_OK_Static_Expression
(N
) then
9795 Val
:= Expr_Value
(N
);
9797 REntry
: constant REnt
:= (Val
, Val
);
9799 Warn_If_Test_Ineffective
(REntry
, N
);
9800 return RList
'(1 => REntry);
9803 -- Identifier (other than static expression) case
9805 else pragma Assert (Nkind (N) in N_Expanded_Name | N_Identifier);
9809 if Is_Type (Entity (N)) then
9811 -- If type has predicates, process them
9813 if Has_Predicates (Entity (N)) then
9814 return Stat_Pred (Entity (N), Static);
9816 -- For static subtype without predicates, get range
9818 elsif Is_OK_Static_Subtype (Entity (N)) then
9819 SLo := Expr_Value (Type_Low_Bound (Entity (N)));
9820 SHi := Expr_Value (Type_High_Bound (Entity (N)));
9821 return RList'(1 => REnt
'(SLo, SHi));
9823 -- Any other type makes us non-static
9826 Static.all := False;
9830 -- Any other kind of identifier in predicate (e.g. a non-static
9831 -- expression value) means this is not a static predicate.
9834 Static.all := False;
9838 end Membership_Entry;
9846 Static : access Boolean) return RList is
9848 -- Not static if type does not have static predicates
9850 if not Has_Static_Predicate (Typ) then
9851 Static.all := False;
9855 -- Otherwise we convert the predicate list to a range list
9858 Spred : constant List_Id := Static_Discrete_Predicate (Typ);
9859 Result : RList (1 .. List_Length (Spred));
9863 P := First (Static_Discrete_Predicate (Typ));
9864 for J in Result'Range loop
9865 Result (J) := REnt'(Lo_Val
(P
), Hi_Val
(P
));
9873 procedure Warn_If_Test_Ineffective
(REntry
: REnt
; N
: Node_Id
) is
9875 procedure IPT_Warning
(Msg
: String);
9881 procedure IPT_Warning
(Msg
: String) is
9883 Error_Msg_N
("ineffective predicate test " & Msg
& "?_s?", N
);
9886 -- Start of processing for Warn_If_Test_Ineffective
9889 -- Do nothing if warning disabled
9891 if not Warn_On_Ineffective_Predicate_Test
then
9894 -- skip null-range corner cases
9896 elsif REntry
.Lo
> REntry
.Hi
or else TLo
> THi
then
9899 -- warn if no overlap between subtype bounds and the given range
9901 elsif REntry
.Lo
> THi
or else REntry
.Hi
< TLo
then
9902 Error_Msg_Uint_1
:= REntry
.Lo
;
9903 if REntry
.Lo
/= REntry
.Hi
then
9904 Error_Msg_Uint_2
:= REntry
.Hi
;
9905 IPT_Warning
("range: ^ .. ^");
9906 elsif Is_Enumeration_Type
(Typ
) and then
9907 Nkind
(N
) in N_Identifier | N_Expanded_Name
9909 IPT_Warning
("value: &");
9911 IPT_Warning
("value: ^");
9914 end Warn_If_Test_Ineffective
;
9916 -- Start of processing for Build_Discrete_Static_Predicate
9919 -- Establish bounds for the predicate
9921 if Compile_Time_Known_Value
(Type_Low_Bound
(Typ
)) then
9922 TLo
:= Expr_Value
(Type_Low_Bound
(Typ
));
9927 if Compile_Time_Known_Value
(Type_High_Bound
(Typ
)) then
9928 THi
:= Expr_Value
(Type_High_Bound
(Typ
));
9933 -- Analyze the expression to see if it is a static predicate
9936 Static
: aliased Boolean := True;
9937 Ranges
: constant RList
:= Get_RList
(Expr
, Static
'Access);
9938 -- Range list from expression if it is static
9943 -- If non-static, return doing nothing
9949 -- Convert range list into a form for the static predicate. In the
9950 -- Ranges array, we just have raw ranges, these must be converted
9951 -- to properly typed and analyzed static expressions or range nodes.
9953 -- Note: here we limit ranges to the ranges of the subtype, so that
9954 -- a predicate is always false for values outside the subtype. That
9955 -- seems fine, such values are invalid anyway, and considering them
9956 -- to fail the predicate seems allowed and friendly, and furthermore
9957 -- simplifies processing for case statements and loops.
9961 for J
in Ranges
'Range loop
9963 Lo
: Uint
:= Ranges
(J
).Lo
;
9964 Hi
: Uint
:= Ranges
(J
).Hi
;
9967 -- Ignore completely out of range entry
9969 if Hi
< TLo
or else Lo
> THi
then
9972 -- Otherwise process entry
9975 -- Adjust out of range value to subtype range
9985 -- Convert range into required form
9987 Append_To
(Plist
, Build_Range
(Lo
, Hi
));
9992 -- Processing was successful and all entries were static, so now we
9993 -- can store the result as the predicate list.
9995 Set_Static_Discrete_Predicate
(Typ
, Plist
);
9997 -- Within a generic the predicate functions themselves need not
10000 if Inside_A_Generic
then
10004 -- The processing for static predicates put the expression into
10005 -- canonical form as a series of ranges. It also eliminated
10006 -- duplicates and collapsed and combined ranges. We might as well
10007 -- replace the alternatives list of the right operand of the
10008 -- membership test with the static predicate list, which will
10009 -- usually be more efficient.
10012 New_Alts
: constant List_Id
:= New_List
;
10013 Old_Node
: Node_Id
;
10014 New_Node
: Node_Id
;
10017 Old_Node
:= First
(Plist
);
10018 while Present
(Old_Node
) loop
10019 New_Node
:= New_Copy
(Old_Node
);
10021 if Nkind
(New_Node
) = N_Range
then
10022 Set_Low_Bound
(New_Node
, New_Copy
(Low_Bound
(Old_Node
)));
10023 Set_High_Bound
(New_Node
, New_Copy
(High_Bound
(Old_Node
)));
10026 Append_To
(New_Alts
, New_Node
);
10030 -- If empty list, replace by False
10032 if Is_Empty_List
(New_Alts
) then
10033 Rewrite
(Expr
, New_Occurrence_Of
(Standard_False
, Loc
));
10035 -- Else replace by set membership test
10040 Left_Opnd
=> Make_Identifier
(Loc
, Nam
),
10041 Right_Opnd
=> Empty
,
10042 Alternatives
=> New_Alts
));
10044 -- Resolve new expression in function context
10046 Push_Scope
(Predicate_Function
(Typ
));
10047 Install_Formals
(Predicate_Function
(Typ
));
10048 Analyze_And_Resolve
(Expr
, Standard_Boolean
);
10053 end Build_Discrete_Static_Predicate
;
10055 --------------------------------
10056 -- Build_Export_Import_Pragma --
10057 --------------------------------
10059 function Build_Export_Import_Pragma
10061 Id
: Entity_Id
) return Node_Id
10063 Asp_Id
: constant Aspect_Id
:= Get_Aspect_Id
(Asp
);
10064 Expr
: constant Node_Id
:= Expression
(Asp
);
10065 Loc
: constant Source_Ptr
:= Sloc
(Asp
);
10069 Conv_Arg
: Node_Id
;
10076 Create_Pragma
: Boolean := False;
10077 -- This flag is set when the aspect form is such that it warrants the
10078 -- creation of a corresponding pragma.
10081 if Present
(Expr
) then
10082 if Error_Posted
(Expr
) then
10085 elsif Is_True
(Expr_Value
(Expr
)) then
10086 Create_Pragma
:= True;
10089 -- Otherwise the aspect defaults to True
10092 Create_Pragma
:= True;
10095 -- Nothing to do when the expression is False or is erroneous
10097 if not Create_Pragma
then
10101 -- Obtain all interfacing aspects that apply to the related entity
10103 Get_Interfacing_Aspects
10107 Expo_Asp
=> Dummy_1
,
10108 Imp_Asp
=> Dummy_2
,
10113 -- Handle the convention argument
10115 if Present
(Conv
) then
10116 Conv_Arg
:= New_Copy_Tree
(Expression
(Conv
));
10118 -- Assume convention "Ada' when aspect Convention is missing
10121 Conv_Arg
:= Make_Identifier
(Loc
, Name_Ada
);
10125 Make_Pragma_Argument_Association
(Loc
,
10126 Chars
=> Name_Convention
,
10127 Expression
=> Conv_Arg
));
10129 -- Handle the entity argument
10132 Make_Pragma_Argument_Association
(Loc
,
10133 Chars
=> Name_Entity
,
10134 Expression
=> New_Occurrence_Of
(Id
, Loc
)));
10136 -- Handle the External_Name argument
10138 if Present
(EN
) then
10140 Make_Pragma_Argument_Association
(Loc
,
10141 Chars
=> Name_External_Name
,
10142 Expression
=> New_Copy_Tree
(Expression
(EN
))));
10145 -- Handle the Link_Name argument
10147 if Present
(LN
) then
10149 Make_Pragma_Argument_Association
(Loc
,
10150 Chars
=> Name_Link_Name
,
10151 Expression
=> New_Copy_Tree
(Expression
(LN
))));
10155 -- pragma Export/Import
10156 -- (Convention => <Conv>/Ada,
10158 -- [External_Name => <EN>,]
10159 -- [Link_Name => <LN>]);
10163 Pragma_Identifier
=>
10164 Make_Identifier
(Loc
, Chars
(Identifier
(Asp
))),
10165 Pragma_Argument_Associations
=> Args
);
10167 -- Decorate the relevant aspect and the pragma
10169 Set_Aspect_Rep_Item
(Asp
, Prag
);
10171 Set_Corresponding_Aspect
(Prag
, Asp
);
10172 Set_From_Aspect_Specification
(Prag
);
10173 Set_Parent
(Prag
, Asp
);
10175 if Asp_Id
= Aspect_Import
and then Is_Subprogram
(Id
) then
10176 Set_Import_Pragma
(Id
, Prag
);
10180 end Build_Export_Import_Pragma
;
10182 ------------------------------
10183 -- Build_Predicate_Function --
10184 ------------------------------
10186 -- The function constructed here has the form:
10188 -- function typPredicate (Ixxx : typ) return Boolean is
10191 -- typ1Predicate (typ1 (Ixxx))
10192 -- and then typ2Predicate (typ2 (Ixxx))
10194 -- and then exp1 and then exp2 and then ...;
10195 -- end typPredicate;
10197 -- If Predicate_Function_Needs_Membership_Parameter is true, then this
10198 -- function takes an additional boolean parameter; the parameter
10199 -- indicates whether the predicate evaluation is part of a membership
10200 -- test. This parameter is used in two cases: 1) It is passed along
10201 -- if another predicate function is called and that predicate function
10202 -- expects to be passed a boolean parameter. 2) If the Predicate_Failure
10203 -- aspect is directly specified for typ, then we replace the return
10204 -- expression described above with
10205 -- (if <expression described above> then True
10206 -- elsif For_Membership_Test then False
10207 -- else (raise Assertion_Error
10208 -- with <Predicate_Failure expression>))
10209 -- Here exp1, and exp2 are expressions from Predicate pragmas. Note that
10210 -- this is the point at which these expressions get analyzed, providing the
10211 -- required delay, and typ1, typ2, are entities from which predicates are
10212 -- inherited. Note that we do NOT generate Check pragmas, that's because we
10213 -- use this function even if checks are off, e.g. for membership tests.
10215 -- Note that the inherited predicates are evaluated first, as required by
10218 -- Note that Sem_Eval.Real_Or_String_Static_Predicate_Matches depends on
10219 -- the form of this return expression.
10221 -- WARNING: This routine manages Ghost regions. Return statements must be
10222 -- replaced by gotos which jump to the end of the routine and restore the
10225 procedure Build_Predicate_Function
(Typ
: Entity_Id
; N
: Node_Id
) is
10226 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
10228 Saved_GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
10229 Saved_IGR
: constant Node_Id
:= Ignored_Ghost_Region
;
10230 -- Save the Ghost-related attributes to restore on exit
10233 -- This is the expression for the result of the function. It is
10234 -- built by connecting the component predicates with AND THEN.
10236 Object_Name
: Name_Id
;
10237 -- Name for argument of Predicate procedure. Note that we use the same
10238 -- name for both predicate functions. That way the reference within the
10239 -- predicate expression is the same in both functions.
10241 Object_Entity
: Entity_Id
;
10242 -- Entity for argument of Predicate procedure
10245 -- The function declaration
10250 Restore_Scope
: Boolean;
10251 -- True if the current scope must be restored on exit
10253 Ancestor_Predicate_Function_Called
: Boolean := False;
10254 -- Does this predicate function include a call to the
10255 -- predication function of an ancestor subtype?
10257 procedure Add_Condition
(Cond
: Node_Id
);
10258 -- Append Cond to Expr using "and then" (or just copy Cond to Expr if
10261 procedure Add_Predicates
;
10262 -- Appends expressions for any Predicate pragmas in the rep item chain
10263 -- Typ to Expr. Note that we look only at items for this exact entity.
10264 -- Inheritance of predicates for the parent type is done by calling the
10265 -- Predicate_Function of the parent type, using Add_Call above.
10267 procedure Add_Call
(T
: Entity_Id
);
10268 -- Includes a call to the predicate function for type T in Expr if
10269 -- Predicate_Function (T) is non-empty.
10271 procedure Replace_Current_Instance_References
10272 (N
: Node_Id
; Typ
, New_Entity
: Entity_Id
);
10273 -- Replace all references to Typ in the tree rooted at N with
10274 -- references to Param. [New_Entity will be a formal parameter of a
10275 -- predicate function.]
10281 procedure Add_Call
(T
: Entity_Id
) is
10285 if Present
(Predicate_Function
(T
)) then
10286 pragma Assert
(Has_Predicates
(Typ
));
10288 -- Build the call to the predicate function of T. The type may be
10289 -- derived, so use an unchecked conversion for the actual.
10292 Dynamic_Mem
: Node_Id
:= Empty
;
10293 Second_Formal
: constant Entity_Id
:=
10294 Next_Entity
(Object_Entity
);
10296 -- Some predicate functions require a second parameter;
10297 -- If one predicate function calls another and the second
10298 -- requires two parameters, then the first should also
10299 -- take two parameters (so that the first function has
10300 -- something to pass to the second function).
10301 if Predicate_Function_Needs_Membership_Parameter
(T
) then
10302 pragma Assert
(Present
(Second_Formal
));
10303 Dynamic_Mem
:= New_Occurrence_Of
(Second_Formal
, Loc
);
10307 Make_Predicate_Call
10310 Unchecked_Convert_To
(T
,
10311 Make_Identifier
(Loc
, Object_Name
)),
10312 Dynamic_Mem
=> Dynamic_Mem
);
10315 -- "and"-in the call to evolving expression
10317 Add_Condition
(Exp
);
10318 Ancestor_Predicate_Function_Called
:= True;
10320 -- Output info message on inheritance if required. Note we do not
10321 -- give this information for generic actual types, since it is
10322 -- unwelcome noise in that case in instantiations. We also
10323 -- generally suppress the message in instantiations, and also
10324 -- if it involves internal names.
10326 if List_Inherited_Aspects
10327 and then not Is_Generic_Actual_Type
(Typ
)
10328 and then Instantiation_Location
(Sloc
(Typ
)) = No_Location
10329 and then not Is_Internal_Name
(Chars
(T
))
10330 and then not Is_Internal_Name
(Chars
(Typ
))
10332 Error_Msg_Sloc
:= Sloc
(Predicate_Function
(T
));
10333 Error_Msg_Node_2
:= T
;
10334 Error_Msg_N
("info: & inherits predicate from & #?.l?", Typ
);
10339 -------------------
10340 -- Add_Condition --
10341 -------------------
10343 procedure Add_Condition
(Cond
: Node_Id
) is
10345 -- This is the first predicate expression
10350 -- Otherwise concatenate to the existing predicate expressions by
10351 -- using "and then".
10355 Make_And_Then
(Loc
,
10356 Left_Opnd
=> Relocate_Node
(Expr
),
10357 Right_Opnd
=> Cond
);
10361 --------------------
10362 -- Add_Predicates --
10363 --------------------
10365 procedure Add_Predicates
is
10366 procedure Add_Predicate
(Prag
: Node_Id
);
10367 -- Concatenate the expression of predicate pragma Prag to Expr by
10368 -- using a short circuit "and then" operator.
10370 -------------------
10371 -- Add_Predicate --
10372 -------------------
10374 procedure Add_Predicate
(Prag
: Node_Id
) is
10377 Asp
: constant Node_Id
:= Corresponding_Aspect
(Prag
);
10381 -- Start of processing for Add_Predicate
10384 -- A ghost predicate is checked only when Ghost mode is enabled.
10385 -- Add a condition for the presence of a predicate to be recorded,
10386 -- which is needed to generate the corresponding predicate
10389 if Is_Ignored_Ghost_Pragma
(Prag
) then
10390 Add_Condition
(New_Occurrence_Of
(Standard_True
, Sloc
(Prag
)));
10394 -- Mark corresponding SCO as enabled
10396 Set_SCO_Pragma_Enabled
(Sloc
(Prag
));
10398 -- Extract the arguments of the pragma
10400 Arg1
:= First
(Pragma_Argument_Associations
(Prag
));
10401 Arg2
:= Next
(Arg1
);
10403 Arg1
:= Get_Pragma_Arg
(Arg1
);
10404 Arg2
:= Get_Pragma_Arg
(Arg2
);
10406 -- When the predicate pragma applies to the current type or its
10407 -- full view, replace all occurrences of the subtype name with
10408 -- references to the formal parameter of the predicate function.
10410 if Entity
(Arg1
) = Typ
10411 or else Full_View
(Entity
(Arg1
)) = Typ
10414 Arg2_Copy
: constant Node_Id
:= New_Copy_Tree
(Arg2
);
10416 Replace_Current_Instance_References
10417 (Arg2_Copy
, Typ
=> Typ
, New_Entity
=> Object_Entity
);
10419 -- If the predicate pragma comes from an aspect, replace the
10420 -- saved expression because we need the subtype references
10421 -- replaced for the calls to Preanalyze_Spec_Expression in
10422 -- Check_Aspect_At_xxx routines.
10424 if Present
(Asp
) then
10425 Set_Expression_Copy
(Asp
, New_Copy_Tree
(Arg2_Copy
));
10428 -- "and"-in the Arg2 condition to evolving expression
10430 Add_Condition
(Arg2_Copy
);
10439 -- Start of processing for Add_Predicates
10442 Ritem
:= First_Rep_Item
(Typ
);
10444 -- If the type is private, check whether full view has inherited
10447 if Is_Private_Type
(Typ
)
10448 and then No
(Ritem
)
10449 and then Present
(Full_View
(Typ
))
10451 Ritem
:= First_Rep_Item
(Full_View
(Typ
));
10454 while Present
(Ritem
) loop
10455 if Nkind
(Ritem
) = N_Pragma
10456 and then Pragma_Name
(Ritem
) = Name_Predicate
10458 Add_Predicate
(Ritem
);
10460 -- If the type is declared in an inner package it may be frozen
10461 -- outside of the package, and the generated pragma has not been
10462 -- analyzed yet, so capture the expression for the predicate
10463 -- function at this point.
10465 elsif Nkind
(Ritem
) = N_Aspect_Specification
10466 and then Present
(Aspect_Rep_Item
(Ritem
))
10467 and then Scope_Depth
(Scope
(Typ
)) > Scope_Depth
(Current_Scope
)
10470 Prag
: constant Node_Id
:= Aspect_Rep_Item
(Ritem
);
10473 if Nkind
(Prag
) = N_Pragma
10474 and then Pragma_Name
(Prag
) = Name_Predicate
10476 Add_Predicate
(Prag
);
10481 Next_Rep_Item
(Ritem
);
10483 end Add_Predicates
;
10485 -----------------------------------------
10486 -- Replace_Current_Instance_References --
10487 -----------------------------------------
10489 procedure Replace_Current_Instance_References
10490 (N
: Node_Id
; Typ
, New_Entity
: Entity_Id
)
10492 Root
: Node_Id
renames N
;
10494 procedure Replace_One_Reference
(N
: Node_Id
);
10495 -- Actual parameter for Replace_Type_References_Generic instance
10497 ---------------------------
10498 -- Replace_One_Reference --
10499 ---------------------------
10501 procedure Replace_One_Reference
(N
: Node_Id
) is
10502 pragma Assert
(In_Subtree
(N
, Root
=> Root
));
10504 Rewrite
(N
, New_Occurrence_Of
(New_Entity
, Sloc
(N
)));
10505 -- Use the Sloc of the usage name, not the defining name
10506 end Replace_One_Reference
;
10508 procedure Replace_Type_References
is
10509 new Replace_Type_References_Generic
(Replace_One_Reference
);
10511 Replace_Type_References
(N
, Typ
);
10512 end Replace_Current_Instance_References
;
10514 -- Start of processing for Build_Predicate_Function
10517 -- Return if already built, if type does not have predicates,
10518 -- or if type is a constructed subtype that will inherit a
10519 -- predicate function from its ancestor. In a generic context
10520 -- the predicated parent may not have a predicate function yet
10521 -- but we don't want to build a new one for the subtype. This can
10522 -- happen in an instance body which is nested within a generic
10523 -- unit, in which case Within_A_Generic may be false, SId is
10524 -- Empty, but uses of Typ will receive a predicate check in a
10525 -- context where expansion and tests are enabled.
10527 SId
:= Predicate_Function
(Typ
);
10528 if not Has_Predicates
(Typ
)
10529 or else (Present
(SId
) and then Has_Completion
(SId
))
10532 and then not Comes_From_Source
(Typ
)
10533 and then Ekind
(Typ
) in E_Array_Subtype
10535 | E_Record_Subtype_With_Private
10536 and then Present
(Predicated_Parent
(Typ
)))
10540 -- Do not generate predicate bodies within a generic unit. The
10541 -- expressions have been analyzed already, and the bodies play no role
10542 -- if not within an executable unit. However, if a static predicate is
10543 -- present it must be processed for legality checks such as case
10544 -- coverage in an expression.
10546 elsif Inside_A_Generic
10547 and then not Has_Static_Predicate_Aspect
(Typ
)
10552 -- Ensure that the declarations are added to the scope of the type
10554 if Scope
(Typ
) /= Current_Scope
then
10555 Push_Scope
(Scope
(Typ
));
10556 Restore_Scope
:= True;
10558 Restore_Scope
:= False;
10561 -- The related type may be subject to pragma Ghost. Set the mode now to
10562 -- ensure that the predicate functions are properly marked as Ghost.
10564 Set_Ghost_Mode
(Typ
);
10566 -- Prepare to construct predicate expression
10570 if Present
(SId
) then
10571 FDecl
:= Unit_Declaration_Node
(SId
);
10574 FDecl
:= Build_Predicate_Function_Declaration
(Typ
);
10575 SId
:= Defining_Entity
(FDecl
);
10578 -- Recover name of formal parameter of function that replaces references
10579 -- to the type in predicate expressions.
10582 Defining_Identifier
10583 (First
(Parameter_Specifications
(Specification
(FDecl
))));
10585 Object_Name
:= Chars
(Object_Entity
);
10587 -- Add predicates for ancestor if present. These must come before the
10588 -- ones for the current type, as required by AI12-0071-1.
10590 -- Looks like predicates aren't added for case of inheriting from
10591 -- multiple progenitors???
10596 Atyp
:= Nearest_Ancestor
(Typ
);
10598 -- The type may be private but the full view may inherit predicates
10600 if No
(Atyp
) and then Is_Private_Type
(Typ
) then
10601 Atyp
:= Nearest_Ancestor
(Full_View
(Typ
));
10604 if Present
(Atyp
) then
10609 -- Add Predicates for the current type
10613 -- Case where predicates are present
10615 if Present
(Expr
) then
10617 -- Build the main predicate function
10620 SIdB
: constant Entity_Id
:=
10621 Make_Defining_Identifier
(Loc
,
10622 Chars
=> New_External_Name
(Chars
(Typ
), "Predicate"));
10623 -- The entity for the function body
10629 Mutate_Ekind
(SIdB
, E_Function
);
10630 Set_Is_Predicate_Function
(SIdB
);
10632 -- Build function body
10635 Param_Specs
: constant List_Id
:= New_List
(
10636 Make_Parameter_Specification
(Loc
,
10637 Defining_Identifier
=>
10638 Make_Defining_Identifier
(Loc
, Object_Name
),
10640 New_Occurrence_Of
(Typ
, Loc
)));
10642 -- if Spec has 2 parameters, then body should too
10643 if Present
(Next_Entity
(Object_Entity
)) then
10644 Append
(Make_Parameter_Specification
(Loc
,
10645 Defining_Identifier
=>
10646 Make_Defining_Identifier
10647 (Loc
, Chars
(Next_Entity
(Object_Entity
))),
10649 New_Occurrence_Of
(Standard_Boolean
, Loc
)),
10654 Make_Function_Specification
(Loc
,
10655 Defining_Unit_Name
=> SIdB
,
10656 Parameter_Specifications
=> Param_Specs
,
10657 Result_Definition
=>
10658 New_Occurrence_Of
(Standard_Boolean
, Loc
));
10661 -- The Predicate_Expression attribute is used by SPARK.
10663 -- If Ancestor_Predicate_Function_Called is True, then
10664 -- we try to exclude that call to the ancestor's
10665 -- predicate function by calling Right_Opnd.
10666 -- The call is not excluded in the case where
10667 -- it is not "and"ed with anything else (so we don't have
10668 -- an N_And_Then node). This exclusion is required if the
10669 -- Predicate_Failure aspect is specified for Typ because
10670 -- in that case we are going to drop the N_And_Then node
10671 -- on the floor. Otherwise, it is a question of what is
10672 -- most convenient for SPARK.
10674 Set_Predicate_Expression
10675 (SId
, (if Ancestor_Predicate_Function_Called
10676 and then Nkind
(Expr
) = N_And_Then
10677 then Right_Opnd
(Expr
)
10681 Result_Expr
: Node_Id
:= Expr
;
10682 PF_Expr
: Node_Id
:= Predicate_Failure_Expression
10683 (Typ
, Inherited_OK
=> False);
10684 PF_Expr_Copy
: Node_Id
;
10685 Second_Formal
: constant Entity_Id
:=
10686 Next_Entity
(Object_Entity
);
10688 -- In GNATprove mode we are only interested in the predicate
10689 -- expression itself and don't want a raise expression that
10690 -- comes from the Predicate_Failure. Ditto for CodePeer.
10691 -- And an illegal Predicate_Failure aspect can lead to cases
10692 -- we want to avoid.
10694 if Present
(PF_Expr
)
10695 and then not GNATprove_Mode
10696 and then not CodePeer_Mode
10697 and then Serious_Errors_Detected
= 0
10699 pragma Assert
(Present
(Second_Formal
));
10701 -- This is an ugly hack to cope with an ugly situation.
10702 -- PF_Expr may have children whose Parent attribute
10703 -- does not point back to PF_Expr. If we pass such a
10704 -- tree to New_Copy_Tree, then it does not make a deep
10705 -- copy. But we need a deep copy. So we need to find a
10706 -- tree for which New_Copy_Tree *will* make a deep copy.
10709 function Check_Node_Parent
(Parent_Node
, Node
: Node_Id
)
10710 return Traverse_Result
;
10711 function Check_Node_Parent
(Parent_Node
, Node
: Node_Id
)
10712 return Traverse_Result
is
10714 if Parent_Node
= PF_Expr
10715 and then not Is_List_Member
(Node
)
10718 (Nkind
(PF_Expr
) = Nkind
(Parent
(Node
)));
10720 -- We need PF_Expr to be a node for which
10721 -- New_Copy_Tree will make a deep copy.
10722 PF_Expr
:= Parent
(Node
);
10726 end Check_Node_Parent
;
10727 procedure Check_Parentage
is
10728 new Traverse_Proc_With_Parent
(Check_Node_Parent
);
10730 Check_Parentage
(PF_Expr
);
10731 PF_Expr_Copy
:= New_Copy_Tree
(PF_Expr
);
10734 -- Current instance uses need to have their Entity
10735 -- fields set so that Replace_Current_Instance_References
10736 -- can find them. So we preanalyze. Just for purposes of
10737 -- calls to Is_Current_Instance during this preanalysis,
10738 -- we set the Parent field.
10739 Set_Parent
(PF_Expr_Copy
, Parent
(PF_Expr
));
10740 Preanalyze
(PF_Expr_Copy
);
10741 Set_Parent
(PF_Expr_Copy
, Empty
);
10743 Replace_Current_Instance_References
10744 (PF_Expr_Copy
, Typ
=> Typ
, New_Entity
=> Object_Entity
);
10746 if Ancestor_Predicate_Function_Called
then
10747 -- If the call to an ancestor predicate function
10748 -- returns False, we do not want to raise an
10749 -- exception here. Our Predicate_Failure aspect does
10750 -- not apply in that case. So we have to build a
10751 -- more complicated result expression:
10752 -- (if not Ancestor_Predicate_Function (...) then False
10753 -- elsif Noninherited_Predicates (...) then True
10754 -- elsif Is_Membership_Test then False
10755 -- else (raise Assertion_Error with PF text))
10758 Ancestor_Call
: constant Node_Id
:=
10759 Left_Opnd
(Result_Expr
);
10760 Local_Preds
: constant Node_Id
:=
10761 Right_Opnd
(Result_Expr
);
10764 Make_If_Expression
(Loc
,
10765 Expressions
=> New_List
(
10766 Make_Op_Not
(Loc
, Ancestor_Call
),
10767 New_Occurrence_Of
(Standard_False
, Loc
),
10768 Make_If_Expression
(Loc
,
10770 Expressions
=> New_List
(
10772 New_Occurrence_Of
(Standard_True
, Loc
),
10773 Make_If_Expression
(Loc
,
10775 Expressions
=> New_List
(
10776 New_Occurrence_Of
(Second_Formal
, Loc
),
10777 New_Occurrence_Of
(Standard_False
, Loc
),
10778 Make_Raise_Expression
(Loc
,
10779 New_Occurrence_Of
(RTE
10780 (RE_Assert_Failure
), Loc
),
10781 PF_Expr_Copy
)))))));
10785 -- Build a conditional expression:
10786 -- (if <predicate evaluates to True> then True
10787 -- elsif Is_Membership_Test then False
10788 -- else (raise Assertion_Error with PF text))
10791 Make_If_Expression
(Loc
,
10792 Expressions
=> New_List
(
10794 New_Occurrence_Of
(Standard_True
, Loc
),
10795 Make_If_Expression
(Loc
,
10797 Expressions
=> New_List
(
10798 New_Occurrence_Of
(Second_Formal
, Loc
),
10799 New_Occurrence_Of
(Standard_False
, Loc
),
10800 Make_Raise_Expression
(Loc
,
10801 New_Occurrence_Of
(RTE
10802 (RE_Assert_Failure
), Loc
),
10808 Make_Subprogram_Body
(Loc
,
10809 Specification
=> Spec
,
10810 Declarations
=> Empty_List
,
10811 Handled_Statement_Sequence
=>
10812 Make_Handled_Sequence_Of_Statements
(Loc
,
10813 Statements
=> New_List
(
10814 Make_Simple_Return_Statement
(Loc
,
10815 Expression
=> Result_Expr
))));
10818 -- The declaration has been analyzed when created, and placed
10819 -- after type declaration. Insert body itself after freeze node,
10820 -- unless subprogram declaration is already there, in which case
10821 -- body better be placed afterwards.
10823 if FDecl
= Next
(N
) then
10824 Insert_After_And_Analyze
(FDecl
, FBody
);
10826 Insert_After_And_Analyze
(N
, FBody
);
10829 -- The defining identifier of a quantified expression carries the
10830 -- scope in which the type appears, but when unnesting we need
10831 -- to indicate that its proper scope is the constructed predicate
10832 -- function. The quantified expressions have been converted into
10833 -- loops during analysis and expansion.
10836 function Reset_Quantified_Variable_Scope
10837 (N
: Node_Id
) return Traverse_Result
;
10839 procedure Reset_Quantified_Variables_Scope
is
10840 new Traverse_Proc
(Reset_Quantified_Variable_Scope
);
10842 -------------------------------------
10843 -- Reset_Quantified_Variable_Scope --
10844 -------------------------------------
10846 function Reset_Quantified_Variable_Scope
10847 (N
: Node_Id
) return Traverse_Result
is
10849 if Nkind
(N
) in N_Iterator_Specification
10850 | N_Loop_Parameter_Specification
10852 Set_Scope
(Defining_Identifier
(N
),
10853 Predicate_Function
(Typ
));
10857 end Reset_Quantified_Variable_Scope
;
10860 if Unnest_Subprogram_Mode
then
10861 Reset_Quantified_Variables_Scope
(Expr
);
10865 -- Within a generic unit, prevent a double analysis of the body
10866 -- which will not be marked analyzed yet. This will happen when
10867 -- the freeze node is created during the preanalysis of an
10868 -- expression function.
10870 if Inside_A_Generic
then
10871 Set_Analyzed
(FBody
);
10874 -- Static predicate functions are always side-effect-free, and
10875 -- in most cases dynamic predicate functions are as well. Mark
10876 -- them as such whenever possible, so redundant predicate checks
10877 -- can be optimized. If there is a variable reference within the
10878 -- expression, the function is not pure.
10880 if Expander_Active
then
10882 Side_Effect_Free
(Expr
, Variable_Ref
=> True));
10883 Set_Is_Inlined
(SId
);
10887 -- See if we have a static predicate. Note that the answer may be
10888 -- yes even if we have an explicit Dynamic_Predicate present.
10895 if not Is_Scalar_Type
(Typ
) and then not Is_String_Type
(Typ
) then
10898 PS
:= Is_Predicate_Static
(Expr
, Object_Name
);
10901 -- Case where we have a predicate-static aspect
10905 -- We don't set Has_Static_Predicate_Aspect, since we can have
10906 -- any of the three cases (Predicate, Dynamic_Predicate, or
10907 -- Static_Predicate) generating a predicate with an expression
10908 -- that is predicate-static. We just indicate that we have a
10909 -- predicate that can be treated as static.
10911 Set_Has_Static_Predicate
(Typ
);
10913 -- For discrete subtype, build the static predicate list
10915 if Is_Discrete_Type
(Typ
) then
10916 Build_Discrete_Static_Predicate
(Typ
, Expr
, Object_Name
);
10918 -- If we don't get a static predicate list, it means that we
10919 -- have a case where this is not possible, most typically in
10920 -- the case where we inherit a dynamic predicate. We do not
10921 -- consider this an error, we just leave the predicate as
10922 -- dynamic. But if we do succeed in building the list, then
10923 -- we mark the predicate as static.
10925 if No
(Static_Discrete_Predicate
(Typ
)) then
10926 Set_Has_Static_Predicate
(Typ
, False);
10929 -- For real or string subtype, save predicate expression
10931 elsif Is_Real_Type
(Typ
) or else Is_String_Type
(Typ
) then
10932 Set_Static_Real_Or_String_Predicate
(Typ
, Expr
);
10935 -- Case of dynamic predicate (expression is not predicate-static)
10938 -- Again, we don't set Has_Dynamic_Predicate_Aspect, since that
10939 -- is only set if we have an explicit Dynamic_Predicate aspect
10940 -- given. Here we may simply have a Predicate aspect where the
10941 -- expression happens not to be predicate-static.
10943 -- Emit an error when the predicate is categorized as static
10944 -- but its expression is not predicate-static.
10946 -- First a little fiddling to get a nice location for the
10947 -- message. If the expression is of the form (A and then B),
10948 -- where A is an inherited predicate, then use the right
10949 -- operand for the Sloc. This avoids getting confused by a call
10950 -- to an inherited predicate with a less convenient source
10954 while Nkind
(EN
) = N_And_Then
10955 and then Nkind
(Left_Opnd
(EN
)) = N_Function_Call
10956 and then Is_Predicate_Function
10957 (Entity
(Name
(Left_Opnd
(EN
))))
10959 EN
:= Right_Opnd
(EN
);
10962 -- Now post appropriate message
10964 if Has_Static_Predicate_Aspect
(Typ
) then
10965 if Is_Scalar_Type
(Typ
) or else Is_String_Type
(Typ
) then
10967 ("expression is not predicate-static (RM 3.2.4(16-22))",
10971 ("static predicate requires scalar or string type", EN
);
10978 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
10980 if Restore_Scope
then
10983 end Build_Predicate_Function
;
10985 ------------------------------------------
10986 -- Build_Predicate_Function_Declaration --
10987 ------------------------------------------
10989 -- WARNING: This routine manages Ghost regions. Return statements must be
10990 -- replaced by gotos which jump to the end of the routine and restore the
10993 function Build_Predicate_Function_Declaration
10994 (Typ
: Entity_Id
) return Node_Id
10996 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
10998 Saved_GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
10999 Saved_IGR
: constant Node_Id
:= Ignored_Ghost_Region
;
11000 -- Save the Ghost-related attributes to restore on exit
11002 Func_Decl
: Node_Id
;
11003 Func_Id
: Entity_Id
;
11006 CRec_Typ
: Entity_Id
;
11007 -- The corresponding record type of Full_Typ
11009 Full_Typ
: Entity_Id
;
11010 -- The full view of Typ
11012 Priv_Typ
: Entity_Id
;
11013 -- The partial view of Typ
11015 UFull_Typ
: Entity_Id
;
11016 -- The underlying full view of Full_Typ
11019 -- The related type may be subject to pragma Ghost. Set the mode now to
11020 -- ensure that the predicate functions are properly marked as Ghost.
11022 Set_Ghost_Mode
(Typ
);
11025 Make_Defining_Identifier
(Loc
,
11026 Chars
=> New_External_Name
(Chars
(Typ
), "Predicate"));
11028 Mutate_Ekind
(Func_Id
, E_Function
);
11029 Set_Etype
(Func_Id
, Standard_Boolean
);
11030 Set_Is_Internal
(Func_Id
);
11031 Set_Is_Predicate_Function
(Func_Id
);
11032 Set_Predicate_Function
(Typ
, Func_Id
);
11034 -- The predicate function requires debug info when the predicates are
11035 -- subject to Source Coverage Obligations.
11037 if Opt
.Generate_SCO
then
11038 Set_Debug_Info_Needed
(Func_Id
);
11041 -- Obtain all views of the input type
11043 Get_Views
(Typ
, Priv_Typ
, Full_Typ
, UFull_Typ
, CRec_Typ
);
11045 -- Associate the predicate function and various flags with all views
11047 Propagate_Predicate_Attributes
(Priv_Typ
, From_Typ
=> Typ
);
11048 Propagate_Predicate_Attributes
(Full_Typ
, From_Typ
=> Typ
);
11049 Propagate_Predicate_Attributes
(UFull_Typ
, From_Typ
=> Typ
);
11050 Propagate_Predicate_Attributes
(CRec_Typ
, From_Typ
=> Typ
);
11053 Param_Specs
: constant List_Id
:= New_List
(
11054 Make_Parameter_Specification
(Loc
,
11055 Defining_Identifier
=> Make_Temporary
(Loc
, 'I'),
11056 Parameter_Type
=> New_Occurrence_Of
(Typ
, Loc
)));
11058 if Predicate_Function_Needs_Membership_Parameter
(Typ
) then
11059 -- Add Boolean-valued For_Membership_Test param
11060 Append
(Make_Parameter_Specification
(Loc
,
11061 Defining_Identifier
=> Make_Temporary
(Loc
, 'M'),
11063 New_Occurrence_Of
(Standard_Boolean
, Loc
)),
11068 Make_Function_Specification
(Loc
,
11069 Defining_Unit_Name
=> Func_Id
,
11070 Parameter_Specifications
=> Param_Specs
,
11071 Result_Definition
=>
11072 New_Occurrence_Of
(Standard_Boolean
, Loc
));
11075 Func_Decl
:= Make_Subprogram_Declaration
(Loc
, Specification
=> Spec
);
11077 Insert_After
(Parent
(Typ
), Func_Decl
);
11078 Analyze
(Func_Decl
);
11080 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
11083 end Build_Predicate_Function_Declaration
;
11085 -----------------------------------------
11086 -- Check_Aspect_At_End_Of_Declarations --
11087 -----------------------------------------
11089 procedure Check_Aspect_At_End_Of_Declarations
(ASN
: Node_Id
) is
11090 Ent
: constant Entity_Id
:= Entity
(ASN
);
11091 Ident
: constant Node_Id
:= Identifier
(ASN
);
11092 A_Id
: constant Aspect_Id
:= Get_Aspect_Id
(Chars
(Ident
));
11094 End_Decl_Expr
: constant Node_Id
:= Expression_Copy
(ASN
);
11095 -- Expression to be analyzed at end of declarations
11097 Freeze_Expr
: constant Node_Id
:= Expression
(ASN
);
11098 -- Expression from call to Check_Aspect_At_Freeze_Point.
11100 T
: constant Entity_Id
:=
11101 (if Present
(Freeze_Expr
) and A_Id
/= Aspect_Stable_Properties
11102 then Etype
(Original_Node
(Freeze_Expr
))
11104 -- Type required for preanalyze call. We use the original expression to
11105 -- get the proper type, to prevent cascaded errors when the expression
11106 -- is constant-folded. For Stable_Properties, the aspect value is
11107 -- not semantically an expression (although it is syntactically);
11108 -- in particular, it has no type.
11111 -- Set True if error
11113 -- On entry to this procedure, Entity (Ident) contains a copy of the
11114 -- original expression from the aspect, saved for this purpose, and
11115 -- but Expression (Ident) is a preanalyzed copy of the expression,
11116 -- preanalyzed just after the freeze point.
11118 procedure Check_Overloaded_Name
;
11119 -- For aspects whose expression is simply a name, this routine checks if
11120 -- the name is overloaded or not. If so, it verifies there is an
11121 -- interpretation that matches the entity obtained at the freeze point,
11122 -- otherwise the compiler complains.
11124 ---------------------------
11125 -- Check_Overloaded_Name --
11126 ---------------------------
11128 procedure Check_Overloaded_Name
is
11130 if not Is_Overloaded
(End_Decl_Expr
) then
11131 Err
:= not Is_Entity_Name
(End_Decl_Expr
)
11132 or else Entity
(End_Decl_Expr
) /= Entity
(Freeze_Expr
);
11138 Index
: Interp_Index
;
11142 Get_First_Interp
(End_Decl_Expr
, Index
, It
);
11143 while Present
(It
.Typ
) loop
11144 if It
.Nam
= Entity
(Freeze_Expr
) then
11149 Get_Next_Interp
(Index
, It
);
11153 end Check_Overloaded_Name
;
11155 -- Start of processing for Check_Aspect_At_End_Of_Declarations
11158 -- In an instance we do not perform the consistency check between freeze
11159 -- point and end of declarations, because it was done already in the
11160 -- analysis of the generic. Furthermore, the delayed analysis of an
11161 -- aspect of the instance may produce spurious errors when the generic
11162 -- is a child unit that references entities in the parent (which might
11163 -- not be in scope at the freeze point of the instance).
11165 if In_Instance
then
11168 -- The enclosing scope may have been rewritten during expansion (.e.g. a
11169 -- task body is rewritten as a procedure) after this conformance check
11170 -- has been performed, so do not perform it again (it may not easily be
11171 -- done if full visibility of local entities is not available).
11173 elsif not Comes_From_Source
(Current_Scope
) then
11176 -- Case of aspects Dimension, Dimension_System and Synchronization
11178 elsif A_Id
= Aspect_Synchronization
then
11181 -- Case of stream attributes and Put_Image, just have to compare
11182 -- entities. However, the expression is just a possibly-overloaded
11183 -- name, so we need to verify that one of these interpretations is
11184 -- the one available at at the freeze point.
11186 elsif A_Id
in Aspect_Input
11192 Analyze
(End_Decl_Expr
);
11193 Check_Overloaded_Name
;
11195 elsif A_Id
in Aspect_Variable_Indexing
11196 | Aspect_Constant_Indexing
11197 | Aspect_Default_Iterator
11198 | Aspect_Iterator_Element
11199 | Aspect_Integer_Literal
11200 | Aspect_Real_Literal
11201 | Aspect_String_Literal
11203 -- Make type unfrozen before analysis, to prevent spurious errors
11204 -- about late attributes.
11206 Set_Is_Frozen
(Ent
, False);
11207 Analyze
(End_Decl_Expr
);
11208 Set_Is_Frozen
(Ent
, True);
11210 -- If the end of declarations comes before any other freeze point,
11211 -- the Freeze_Expr is not analyzed: no check needed.
11213 if Analyzed
(Freeze_Expr
) and then not In_Instance
then
11214 Check_Overloaded_Name
;
11222 -- In a generic context freeze nodes are not always generated, so
11223 -- analyze the expression now. If the aspect is for a type, we must
11224 -- also make its potential components accessible.
11226 if not Analyzed
(Freeze_Expr
) and then Inside_A_Generic
then
11227 if A_Id
in Aspect_Dynamic_Predicate
11228 | Aspect_Ghost_Predicate
11230 | Aspect_Static_Predicate
11233 Preanalyze_Spec_Expression
(Freeze_Expr
, Standard_Boolean
);
11236 elsif A_Id
= Aspect_Priority
then
11238 Preanalyze_Spec_Expression
(Freeze_Expr
, Any_Integer
);
11242 Preanalyze
(Freeze_Expr
);
11246 -- Indicate that the expression comes from an aspect specification,
11247 -- which is used in subsequent analysis even if expansion is off.
11249 if Present
(End_Decl_Expr
) then
11250 Set_Parent
(End_Decl_Expr
, ASN
);
11253 -- In a generic context the original aspect expressions have not
11254 -- been preanalyzed, so do it now. There are no conformance checks
11255 -- to perform in this case. As before, we have to make components
11256 -- visible for aspects that may reference them.
11258 if Present
(Freeze_Expr
) and then No
(T
) then
11259 if A_Id
in Aspect_Dynamic_Predicate
11260 | Aspect_Ghost_Predicate
11263 | Aspect_Static_Predicate
11266 Check_Aspect_At_Freeze_Point
(ASN
);
11270 Check_Aspect_At_Freeze_Point
(ASN
);
11274 -- The default values attributes may be defined in the private part,
11275 -- and the analysis of the expression may take place when only the
11276 -- partial view is visible. The expression must be scalar, so use
11277 -- the full view to resolve.
11279 elsif A_Id
in Aspect_Default_Component_Value | Aspect_Default_Value
11280 and then Is_Private_Type
(T
)
11282 Preanalyze_Spec_Expression
(End_Decl_Expr
, Full_View
(T
));
11284 -- The following aspect expressions may contain references to
11285 -- components and discriminants of the type.
11287 elsif A_Id
in Aspect_CPU
11288 | Aspect_Dynamic_Predicate
11289 | Aspect_Ghost_Predicate
11292 | Aspect_Static_Predicate
11295 Preanalyze_Spec_Expression
(End_Decl_Expr
, T
);
11298 elsif A_Id
= Aspect_Predicate_Failure
then
11299 Preanalyze_Spec_Expression
(End_Decl_Expr
, Standard_String
);
11300 elsif Present
(End_Decl_Expr
) then
11301 Preanalyze_Spec_Expression
(End_Decl_Expr
, T
);
11305 not Fully_Conformant_Expressions
11306 (End_Decl_Expr
, Freeze_Expr
, Report
=> True);
11309 -- Output error message if error. Force error on aspect specification
11310 -- even if there is an error on the expression itself.
11314 ("!visibility of aspect for& changes after freeze point",
11317 ("info: & is frozen here, (RM 13.1.1 (13/3))??",
11318 Freeze_Node
(Ent
), Ent
);
11320 end Check_Aspect_At_End_Of_Declarations
;
11322 ----------------------------------
11323 -- Check_Aspect_At_Freeze_Point --
11324 ----------------------------------
11326 procedure Check_Aspect_At_Freeze_Point
(ASN
: Node_Id
) is
11327 Ident
: constant Node_Id
:= Identifier
(ASN
);
11328 -- Identifier (use Entity field to save expression)
11330 Expr
: constant Node_Id
:= Expression
(ASN
);
11331 -- For cases where using Entity (Identifier) doesn't work
11333 A_Id
: constant Aspect_Id
:= Get_Aspect_Id
(Chars
(Ident
));
11335 T
: Entity_Id
:= Empty
;
11336 -- Type required for preanalyze call
11339 -- On entry to this procedure, Entity (Ident) contains a copy of the
11340 -- original expression from the aspect, saved for this purpose.
11342 -- On exit from this procedure Entity (Ident) is unchanged, still
11343 -- containing that copy, but Expression (Ident) is a preanalyzed copy
11344 -- of the expression, preanalyzed just after the freeze point.
11346 -- Make a copy of the expression to be preanalyzed
11348 Set_Expression
(ASN
, New_Copy_Tree
(Expression_Copy
(ASN
)));
11350 -- Find type for preanalyze call
11354 -- No_Aspect should be impossible
11357 raise Program_Error
;
11359 -- Aspects taking an optional boolean argument
11361 when Boolean_Aspects
11362 | Library_Unit_Aspects
11364 T
:= Standard_Boolean
;
11366 -- Aspects corresponding to attribute definition clauses
11368 when Aspect_Address
=>
11369 T
:= RTE
(RE_Address
);
11371 when Aspect_Attach_Handler
=>
11372 T
:= RTE
(RE_Interrupt_ID
);
11374 when Aspect_Bit_Order
11375 | Aspect_Scalar_Storage_Order
11377 T
:= RTE
(RE_Bit_Order
);
11379 when Aspect_Convention
=>
11383 T
:= RTE
(RE_CPU_Range
);
11385 -- Default_Component_Value is resolved with the component type
11387 when Aspect_Default_Component_Value
=>
11388 T
:= Component_Type
(Entity
(ASN
));
11390 when Aspect_Default_Storage_Pool
=>
11391 T
:= Class_Wide_Type
(RTE
(RE_Root_Storage_Pool
));
11393 -- Default_Value is resolved with the type entity in question
11395 when Aspect_Default_Value
=>
11398 when Aspect_Dispatching_Domain
=>
11399 T
:= RTE
(RE_Dispatching_Domain
);
11401 when Aspect_External_Tag
=>
11402 T
:= Standard_String
;
11404 when Aspect_External_Name
=>
11405 T
:= Standard_String
;
11407 when Aspect_Link_Name
=>
11408 T
:= Standard_String
;
11410 when Aspect_Interrupt_Priority
11413 T
:= Standard_Integer
;
11415 when Aspect_Relative_Deadline
=>
11416 T
:= RTE
(RE_Time_Span
);
11418 when Aspect_Secondary_Stack_Size
=>
11419 T
:= Standard_Integer
;
11421 when Aspect_Small
=>
11423 -- Note that the expression can be of any real type (not just a
11424 -- real universal literal) as long as it is a static constant.
11428 -- For a simple storage pool, we have to retrieve the type of the
11429 -- pool object associated with the aspect's corresponding attribute
11430 -- definition clause.
11432 when Aspect_Simple_Storage_Pool
=>
11433 T
:= Etype
(Expression
(Aspect_Rep_Item
(ASN
)));
11435 when Aspect_Storage_Pool
=>
11436 T
:= Class_Wide_Type
(RTE
(RE_Root_Storage_Pool
));
11438 when Aspect_Alignment
11439 | Aspect_Component_Size
11440 | Aspect_Machine_Radix
11441 | Aspect_Object_Size
11443 | Aspect_Storage_Size
11444 | Aspect_Stream_Size
11445 | Aspect_Value_Size
11449 when Aspect_Linker_Section
=>
11450 T
:= Standard_String
;
11452 when Aspect_Local_Restrictions
=>
11455 when Aspect_Synchronization
=>
11458 -- Special case, the expression of these aspects is just an entity
11459 -- that does not need any resolution, so just analyze.
11468 Analyze
(Expression
(ASN
));
11471 -- Same for Iterator aspects, where the expression is a function
11472 -- name. Legality rules are checked separately.
11474 when Aspect_Constant_Indexing
11475 | Aspect_Default_Iterator
11476 | Aspect_Iterator_Element
11477 | Aspect_Variable_Indexing
11479 Analyze
(Expression
(ASN
));
11482 -- Same for Literal aspects, where the expression is a function
11483 -- name. Legality rules are checked separately. Use Expr to avoid
11484 -- losing track of the previous resolution of Expression.
11486 when Aspect_Integer_Literal
11487 | Aspect_Real_Literal
11488 | Aspect_String_Literal
11490 Set_Entity
(Expression
(ASN
), Entity
(Expr
));
11491 Set_Etype
(Expression
(ASN
), Etype
(Expr
));
11492 Set_Is_Overloaded
(Expression
(ASN
), False);
11493 Analyze
(Expression
(ASN
));
11496 -- Ditto for Iterable, legality checks in Validate_Iterable_Aspect.
11498 when Aspect_Iterable
=>
11502 Cursor
: constant Entity_Id
:= Get_Cursor_Type
(ASN
, T
);
11507 if Cursor
= Any_Type
then
11511 Assoc
:= First
(Component_Associations
(Expression
(ASN
)));
11512 while Present
(Assoc
) loop
11513 Expr
:= Expression
(Assoc
);
11516 if not Error_Posted
(Expr
) then
11517 Resolve_Iterable_Operation
11518 (Expr
, Cursor
, T
, Chars
(First
(Choices
(Assoc
))));
11527 when Aspect_Aggregate
=>
11528 if Is_Array_Type
(Entity
(ASN
)) then
11530 ("aspect& can only be applied to non-array type",
11533 Resolve_Aspect_Aggregate
(Entity
(ASN
), Expression
(ASN
));
11536 when Aspect_Stable_Properties
=>
11537 Resolve_Aspect_Stable_Properties
11538 (Entity
(ASN
), Expression
(ASN
),
11539 Class_Present
=> Class_Present
(ASN
));
11542 -- Invariant/Predicate take boolean expressions
11544 when Aspect_Dynamic_Predicate
11546 | Aspect_Ghost_Predicate
11548 | Aspect_Static_Predicate
11549 | Aspect_Type_Invariant
11551 T
:= Standard_Boolean
;
11553 when Aspect_Predicate_Failure
=>
11554 T
:= Standard_String
;
11556 -- As for some other aspects above, the expression of this aspect is
11557 -- just an entity that does not need any resolution, so just analyze.
11559 when Aspect_Designated_Storage_Model
=>
11560 Analyze
(Expression
(ASN
));
11563 when Aspect_Storage_Model_Type
=>
11565 -- The aggregate argument of Storage_Model_Type is optional, and
11566 -- when not present the aspect defaults to the native storage
11567 -- model (where the address type is System.Address, and other
11568 -- arguments default to corresponding native storage operations).
11570 if No
(Expression
(ASN
)) then
11579 Addr_Type
: Entity_Id
:= Empty
;
11582 Assoc
:= First
(Component_Associations
(Expression
(ASN
)));
11583 while Present
(Assoc
) loop
11584 Expr
:= Expression
(Assoc
);
11587 if not Error_Posted
(Expr
) then
11588 Resolve_Storage_Model_Type_Argument
11589 (Expr
, T
, Addr_Type
, Chars
(First
(Choices
(Assoc
))));
11598 -- Here is the list of aspects that don't require delay analysis
11600 when Aspect_Abstract_State
11601 | Aspect_Always_Terminates
11603 | Aspect_Async_Readers
11604 | Aspect_Async_Writers
11605 | Aspect_Constant_After_Elaboration
11606 | Aspect_Contract_Cases
11607 | Aspect_Default_Initial_Condition
11610 | Aspect_Dimension_System
11611 | Aspect_Exceptional_Cases
11612 | Aspect_Effective_Reads
11613 | Aspect_Effective_Writes
11614 | Aspect_Extensions_Visible
11617 | Aspect_GNAT_Annotate
11618 | Aspect_Implicit_Dereference
11619 | Aspect_Initial_Condition
11620 | Aspect_Initializes
11621 | Aspect_Max_Entry_Queue_Depth
11622 | Aspect_Max_Entry_Queue_Length
11623 | Aspect_Max_Queue_Length
11624 | Aspect_No_Caching
11625 | Aspect_No_Controlled_Parts
11626 | Aspect_No_Task_Parts
11627 | Aspect_Obsolescent
11630 | Aspect_Postcondition
11632 | Aspect_Precondition
11633 | Aspect_Side_Effects
11634 | Aspect_Refined_Depends
11635 | Aspect_Refined_Global
11636 | Aspect_Refined_Post
11637 | Aspect_Refined_State
11638 | Aspect_Relaxed_Initialization
11639 | Aspect_SPARK_Mode
11640 | Aspect_Subprogram_Variant
11643 | Aspect_Unimplemented
11644 | Aspect_Unsuppress
11645 | Aspect_User_Aspect
11646 | Aspect_Volatile_Function
11648 raise Program_Error
;
11652 -- Do the preanalyze call
11654 if Present
(Expression
(ASN
)) then
11655 Preanalyze_Spec_Expression
(Expression
(ASN
), T
);
11657 end Check_Aspect_At_Freeze_Point
;
11659 -----------------------------------
11660 -- Check_Constant_Address_Clause --
11661 -----------------------------------
11663 procedure Check_Constant_Address_Clause
11667 procedure Check_At_Constant_Address
(Nod
: Node_Id
);
11668 -- Checks that the given node N represents a name whose 'Address is
11669 -- constant (in the same sense as OK_Constant_Address_Clause, i.e. the
11670 -- address value is the same at the point of declaration of U_Ent and at
11671 -- the time of elaboration of the address clause.
11673 procedure Check_Expr_Constants
(Nod
: Node_Id
);
11674 -- Checks that Nod meets the requirements for a constant address clause
11675 -- in the sense of the enclosing procedure.
11677 procedure Check_List_Constants
(Lst
: List_Id
);
11678 -- Check that all elements of list Lst meet the requirements for a
11679 -- constant address clause in the sense of the enclosing procedure.
11681 -------------------------------
11682 -- Check_At_Constant_Address --
11683 -------------------------------
11685 procedure Check_At_Constant_Address
(Nod
: Node_Id
) is
11687 if Is_Entity_Name
(Nod
) then
11688 if Present
(Address_Clause
(Entity
((Nod
)))) then
11690 ("invalid address clause for initialized object &!",
11693 ("address for& cannot depend on another address clause! "
11694 & "(RM 13.1(22))!", Nod
, U_Ent
);
11696 elsif In_Same_Source_Unit
(Entity
(Nod
), U_Ent
)
11697 and then Sloc
(U_Ent
) < Sloc
(Entity
(Nod
))
11700 ("invalid address clause for initialized object &!",
11702 Error_Msg_Node_2
:= U_Ent
;
11704 ("\& must be defined before & (RM 13.1(22))!",
11705 Nod
, Entity
(Nod
));
11708 elsif Nkind
(Nod
) = N_Selected_Component
then
11710 T
: constant Entity_Id
:= Etype
(Prefix
(Nod
));
11713 if (Is_Record_Type
(T
)
11714 and then Has_Discriminants
(T
))
11716 (Is_Access_Type
(T
)
11717 and then Is_Record_Type
(Designated_Type
(T
))
11718 and then Has_Discriminants
(Designated_Type
(T
)))
11721 ("invalid address clause for initialized object &!",
11724 ("\address cannot depend on component of discriminated "
11725 & "record (RM 13.1(22))!", Nod
);
11727 Check_At_Constant_Address
(Prefix
(Nod
));
11731 elsif Nkind
(Nod
) = N_Indexed_Component
then
11732 Check_At_Constant_Address
(Prefix
(Nod
));
11733 Check_List_Constants
(Expressions
(Nod
));
11736 Check_Expr_Constants
(Nod
);
11738 end Check_At_Constant_Address
;
11740 --------------------------
11741 -- Check_Expr_Constants --
11742 --------------------------
11744 procedure Check_Expr_Constants
(Nod
: Node_Id
) is
11745 Loc_U_Ent
: constant Source_Ptr
:= Sloc
(U_Ent
);
11746 Ent
: Entity_Id
:= Empty
;
11749 if Nkind
(Nod
) in N_Has_Etype
11750 and then Etype
(Nod
) = Any_Type
11755 case Nkind
(Nod
) is
11761 when N_Expanded_Name
11764 Ent
:= Entity
(Nod
);
11766 -- We need to look at the original node if it is different
11767 -- from the node, since we may have rewritten things and
11768 -- substituted an identifier representing the rewrite.
11770 if Is_Rewrite_Substitution
(Nod
) then
11771 Check_Expr_Constants
(Original_Node
(Nod
));
11773 -- If the node is an object declaration without initial
11774 -- value, some code has been expanded, and the expression
11775 -- is not constant, even if the constituents might be
11776 -- acceptable, as in A'Address + offset.
11778 if Ekind
(Ent
) = E_Variable
11780 Nkind
(Declaration_Node
(Ent
)) = N_Object_Declaration
11782 No
(Expression
(Declaration_Node
(Ent
)))
11785 ("invalid address clause for initialized object &!",
11788 -- If entity is constant, it may be the result of expanding
11789 -- a check. We must verify that its declaration appears
11790 -- before the object in question, else we also reject the
11793 elsif Ekind
(Ent
) = E_Constant
11794 and then In_Same_Source_Unit
(Ent
, U_Ent
)
11795 and then Sloc
(Ent
) > Loc_U_Ent
11798 ("invalid address clause for initialized object &!",
11805 -- Otherwise look at the identifier and see if it is OK
11807 if Is_Named_Number
(Ent
) or else Is_Type
(Ent
) then
11810 elsif Ekind
(Ent
) in E_Constant | E_In_Parameter
then
11812 -- This is the case where we must have Ent defined before
11813 -- U_Ent. Clearly if they are in different units this
11814 -- requirement is met since the unit containing Ent is
11815 -- already processed.
11817 if not In_Same_Source_Unit
(Ent
, U_Ent
) then
11820 -- Otherwise location of Ent must be before the location
11821 -- of U_Ent, that's what prior defined means.
11823 elsif Sloc
(Ent
) < Loc_U_Ent
then
11828 ("invalid address clause for initialized object &!",
11830 Error_Msg_Node_2
:= U_Ent
;
11832 ("\& must be defined before & (RM 13.1(22))!",
11836 elsif Nkind
(Original_Node
(Nod
)) = N_Function_Call
then
11837 Check_Expr_Constants
(Original_Node
(Nod
));
11841 ("invalid address clause for initialized object &!",
11844 if Comes_From_Source
(Ent
) then
11846 ("\reference to variable& not allowed"
11847 & " (RM 13.1(22))!", Nod
, Ent
);
11850 ("non-static expression not allowed"
11851 & " (RM 13.1(22))!", Nod
);
11855 when N_Integer_Literal
=>
11857 -- If this is a rewritten unchecked conversion, in a system
11858 -- where Address is an integer type, always use the base type
11859 -- for a literal value. This is user-friendly and prevents
11860 -- order-of-elaboration issues with instances of unchecked
11863 if Nkind
(Original_Node
(Nod
)) = N_Function_Call
then
11864 Set_Etype
(Nod
, Base_Type
(Etype
(Nod
)));
11867 when N_Character_Literal
11874 Check_Expr_Constants
(Low_Bound
(Nod
));
11875 Check_Expr_Constants
(High_Bound
(Nod
));
11877 when N_Explicit_Dereference
=>
11878 Check_Expr_Constants
(Prefix
(Nod
));
11880 when N_Indexed_Component
=>
11881 Check_Expr_Constants
(Prefix
(Nod
));
11882 Check_List_Constants
(Expressions
(Nod
));
11885 Check_Expr_Constants
(Prefix
(Nod
));
11886 Check_Expr_Constants
(Discrete_Range
(Nod
));
11888 when N_Selected_Component
=>
11889 Check_Expr_Constants
(Prefix
(Nod
));
11891 when N_Attribute_Reference
=>
11892 if Attribute_Name
(Nod
) in Name_Address
11894 | Name_Unchecked_Access
11895 | Name_Unrestricted_Access
11897 Check_At_Constant_Address
(Prefix
(Nod
));
11899 -- Normally, System'To_Address will have been transformed into
11900 -- an Unchecked_Conversion, but in -gnatc mode, it will not,
11901 -- and we don't want to give an error, because the whole point
11902 -- of 'To_Address is that it is static.
11904 elsif Attribute_Name
(Nod
) = Name_To_Address
then
11905 pragma Assert
(Operating_Mode
= Check_Semantics
);
11909 Check_Expr_Constants
(Prefix
(Nod
));
11910 Check_List_Constants
(Expressions
(Nod
));
11913 when N_Aggregate
=>
11914 Check_List_Constants
(Component_Associations
(Nod
));
11915 Check_List_Constants
(Expressions
(Nod
));
11917 when N_Component_Association
=>
11918 Check_Expr_Constants
(Expression
(Nod
));
11920 when N_Extension_Aggregate
=>
11921 Check_Expr_Constants
(Ancestor_Part
(Nod
));
11922 Check_List_Constants
(Component_Associations
(Nod
));
11923 Check_List_Constants
(Expressions
(Nod
));
11929 | N_Membership_Test
11932 Check_Expr_Constants
(Left_Opnd
(Nod
));
11933 Check_Expr_Constants
(Right_Opnd
(Nod
));
11936 Check_Expr_Constants
(Right_Opnd
(Nod
));
11939 | N_Qualified_Expression
11940 | N_Type_Conversion
11941 | N_Unchecked_Type_Conversion
11943 Check_Expr_Constants
(Expression
(Nod
));
11945 when N_Function_Call
=>
11946 if not Is_Pure
(Entity
(Name
(Nod
))) then
11948 ("invalid address clause for initialized object &!",
11952 ("\function & is not pure (RM 13.1(22))!",
11953 Nod
, Entity
(Name
(Nod
)));
11956 Check_List_Constants
(Parameter_Associations
(Nod
));
11959 when N_Parameter_Association
=>
11960 Check_Expr_Constants
(Explicit_Actual_Parameter
(Nod
));
11964 ("invalid address clause for initialized object &!",
11967 ("\must be constant defined before& (RM 13.1(22))!",
11970 end Check_Expr_Constants
;
11972 --------------------------
11973 -- Check_List_Constants --
11974 --------------------------
11976 procedure Check_List_Constants
(Lst
: List_Id
) is
11980 Nod1
:= First
(Lst
);
11981 while Present
(Nod1
) loop
11982 Check_Expr_Constants
(Nod1
);
11985 end Check_List_Constants
;
11987 -- Start of processing for Check_Constant_Address_Clause
11990 -- If rep_clauses are to be ignored, no need for legality checks. In
11991 -- particular, no need to pester user about rep clauses that violate the
11992 -- rule on constant addresses, given that these clauses will be removed
11993 -- by Freeze before they reach the back end. Similarly in CodePeer mode,
11994 -- we want to relax these checks.
11996 if not Ignore_Rep_Clauses
and not CodePeer_Mode
then
11997 Check_Expr_Constants
(Expr
);
11999 end Check_Constant_Address_Clause
;
12001 ---------------------------
12002 -- Check_Pool_Size_Clash --
12003 ---------------------------
12005 procedure Check_Pool_Size_Clash
(Ent
: Entity_Id
; SP
, SS
: Node_Id
) is
12009 -- We need to find out which one came first. Note that in the case of
12010 -- aspects mixed with pragmas there are cases where the processing order
12011 -- is reversed, which is why we do the check here.
12013 if Sloc
(SP
) < Sloc
(SS
) then
12014 Error_Msg_Sloc
:= Sloc
(SP
);
12016 Error_Msg_NE
("Storage_Pool previously given for&#", Post
, Ent
);
12019 Error_Msg_Sloc
:= Sloc
(SS
);
12021 Error_Msg_NE
("Storage_Size previously given for&#", Post
, Ent
);
12025 ("\cannot have Storage_Size and Storage_Pool (RM 13.11(3))", Post
);
12026 end Check_Pool_Size_Clash
;
12028 ----------------------------------------
12029 -- Check_Record_Representation_Clause --
12030 ----------------------------------------
12032 procedure Check_Record_Representation_Clause
(N
: Node_Id
) is
12033 Loc
: constant Source_Ptr
:= Sloc
(N
);
12034 Ident
: constant Node_Id
:= Identifier
(N
);
12035 Rectype
: Entity_Id
;
12038 Fbit
: Uint
:= No_Uint
;
12039 Lbit
: Uint
:= No_Uint
;
12040 Hbit
: Uint
:= Uint_0
;
12044 Max_Bit_So_Far
: Uint
;
12045 -- Records the maximum bit position so far. If all field positions
12046 -- are monotonically increasing, then we can skip the circuit for
12047 -- checking for overlap, since no overlap is possible.
12049 Tagged_Parent
: Entity_Id
:= Empty
;
12050 -- This is set in the case of an extension for which we have either a
12051 -- size clause or Is_Fully_Repped_Tagged_Type True (indicating that all
12052 -- components are positioned by record representation clauses) on the
12053 -- parent type. In this case we check for overlap between components of
12054 -- this tagged type and the parent component. Tagged_Parent will point
12055 -- to this parent type. For all other cases, Tagged_Parent is Empty.
12057 Parent_Last_Bit
: Uint
:= No_Uint
; -- init to avoid warning
12058 -- Relevant only if Tagged_Parent is set, Parent_Last_Bit indicates the
12059 -- last bit position for any field in the parent type. We only need to
12060 -- check overlap for fields starting below this point.
12062 Overlap_Check_Required
: Boolean;
12063 -- Used to keep track of whether or not an overlap check is required
12065 Overlap_Detected
: Boolean := False;
12066 -- Set True if an overlap is detected
12068 Ccount
: Natural := 0;
12069 -- Number of component clauses in record rep clause
12071 procedure Check_Component_Overlap
(C1_Ent
, C2_Ent
: Entity_Id
);
12072 -- Given two entities for record components or discriminants, checks
12073 -- if they have overlapping component clauses and issues errors if so.
12075 procedure Find_Component
;
12076 -- Finds component entity corresponding to current component clause (in
12077 -- CC), and sets Comp to the entity, and Fbit/Lbit to the zero origin
12078 -- start/stop bits for the field. If there is no matching component or
12079 -- if the matching component does not have a component clause, then
12080 -- that's an error and Comp is set to Empty, but no error message is
12081 -- issued, since the message was already given. Comp is also set to
12082 -- Empty if the current "component clause" is in fact a pragma.
12084 procedure Record_Hole_Check
12085 (Rectype
: Entity_Id
; After_Last
: out Uint
; Warn
: Boolean);
12086 -- Checks for gaps in the given Rectype. Compute After_Last, the bit
12087 -- number after the last component. Warn is True on the initial call,
12088 -- and warnings are given for gaps. For a type extension, this is called
12089 -- recursively to compute After_Last for the parent type; in this case
12090 -- Warn is False and the warnings are suppressed.
12092 procedure Component_Order_Check
(Rectype
: Entity_Id
);
12093 -- Check that the order of component clauses agrees with the order of
12094 -- component declarations, and that the component clauses are given in
12095 -- increasing order of bit offset.
12097 -----------------------------
12098 -- Check_Component_Overlap --
12099 -----------------------------
12101 procedure Check_Component_Overlap
(C1_Ent
, C2_Ent
: Entity_Id
) is
12102 CC1
: constant Node_Id
:= Component_Clause
(C1_Ent
);
12103 CC2
: constant Node_Id
:= Component_Clause
(C2_Ent
);
12106 if Present
(CC1
) and then Present
(CC2
) then
12108 -- Exclude odd case where we have two tag components in the same
12109 -- record, both at location zero. This seems a bit strange, but
12110 -- it seems to happen in some circumstances, perhaps on an error.
12112 if Chars
(C1_Ent
) = Name_uTag
then
12116 -- Here we check if the two fields overlap
12119 S1
: constant Uint
:= Component_Bit_Offset
(C1_Ent
);
12120 S2
: constant Uint
:= Component_Bit_Offset
(C2_Ent
);
12121 E1
: constant Uint
:= S1
+ Esize
(C1_Ent
);
12122 E2
: constant Uint
:= S2
+ Esize
(C2_Ent
);
12125 if E2
<= S1
or else E1
<= S2
then
12128 Error_Msg_Node_2
:= Component_Name
(CC2
);
12129 Error_Msg_Sloc
:= Sloc
(Error_Msg_Node_2
);
12130 Error_Msg_Node_1
:= Component_Name
(CC1
);
12132 ("component& overlaps & #", Component_Name
(CC1
));
12133 Overlap_Detected
:= True;
12137 end Check_Component_Overlap
;
12139 ---------------------------
12140 -- Component_Order_Check --
12141 ---------------------------
12143 procedure Component_Order_Check
(Rectype
: Entity_Id
) is
12144 Comp
: Entity_Id
:= First_Component
(Rectype
);
12145 Clause
: Node_Id
:= First
(Component_Clauses
(N
));
12146 Prev_Bit_Offset
: Uint
:= Uint_0
;
12147 OOO
: constant String :=
12148 "?_r?component clause out of order with respect to declaration";
12151 -- Step Comp through components and Clause through component clauses,
12152 -- skipping pragmas. We ignore discriminants and variant parts,
12153 -- because we get most of the benefit from the plain vanilla
12154 -- component cases, without the extra complexity. If we find a Comp
12155 -- and Clause that don't match, give a warning on both and quit. If
12156 -- we find two subsequent clauses out of order by bit layout, give
12157 -- warning and quit. On each iteration, Prev_Bit_Offset is the one
12158 -- from the previous iteration (or 0 to start).
12160 while Present
(Comp
) and then Present
(Clause
) loop
12161 if Nkind
(Clause
) = N_Component_Clause
12162 and then Ekind
(Entity
(Component_Name
(Clause
))) = E_Component
12164 if Entity
(Component_Name
(Clause
)) /= Comp
then
12165 Error_Msg_N
(OOO
, Comp
);
12166 Error_Msg_N
(OOO
, Clause
);
12170 if not Reverse_Bit_Order
(Rectype
)
12171 and then not Reverse_Storage_Order
(Rectype
)
12172 and then Component_Bit_Offset
(Comp
) < Prev_Bit_Offset
12174 Error_Msg_N
("?_r?memory layout out of order", Clause
);
12178 Prev_Bit_Offset
:= Component_Bit_Offset
(Comp
);
12179 Next_Component
(Comp
);
12184 end Component_Order_Check
;
12186 --------------------
12187 -- Find_Component --
12188 --------------------
12190 procedure Find_Component
is
12192 procedure Search_Component
(R
: Entity_Id
);
12193 -- Search components of R for a match. If found, Comp is set
12195 ----------------------
12196 -- Search_Component --
12197 ----------------------
12199 procedure Search_Component
(R
: Entity_Id
) is
12201 Comp
:= First_Component_Or_Discriminant
(R
);
12202 while Present
(Comp
) loop
12204 -- Ignore error of attribute name for component name (we
12205 -- already gave an error message for this, so no need to
12208 if Nkind
(Component_Name
(CC
)) = N_Attribute_Reference
then
12211 exit when Chars
(Comp
) = Chars
(Component_Name
(CC
));
12214 Next_Component_Or_Discriminant
(Comp
);
12216 end Search_Component
;
12218 -- Start of processing for Find_Component
12221 -- Return with Comp set to Empty if we have a pragma
12223 if Nkind
(CC
) = N_Pragma
then
12228 -- Search current record for matching component
12230 Search_Component
(Rectype
);
12232 -- If not found, maybe component of base type discriminant that is
12233 -- absent from statically constrained first subtype.
12236 Search_Component
(Base_Type
(Rectype
));
12239 -- If no component, or the component does not reference the component
12240 -- clause in question, then there was some previous error for which
12241 -- we already gave a message, so just return with Comp Empty.
12243 if No
(Comp
) or else Component_Clause
(Comp
) /= CC
then
12244 Check_Error_Detected
;
12247 -- Normal case where we have a component clause
12250 Fbit
:= Component_Bit_Offset
(Comp
);
12251 Lbit
:= Fbit
+ Esize
(Comp
) - 1;
12253 end Find_Component
;
12255 -----------------------
12256 -- Record_Hole_Check --
12257 -----------------------
12259 procedure Record_Hole_Check
12260 (Rectype
: Entity_Id
; After_Last
: out Uint
; Warn
: Boolean)
12262 Decl
: constant Node_Id
:= Declaration_Node
(Base_Type
(Rectype
));
12263 -- Full declaration of record type
12265 procedure Check_Component_List
12270 -- Check component list CL for holes. DS is a list of discriminant
12271 -- specifications to be included in the consideration of components.
12272 -- Sbit is the starting bit, which is zero if there are no preceding
12273 -- components (before a variant part, or a parent type, or a tag
12274 -- field). If there are preceding components, Sbit is the bit just
12275 -- after the last such component. Abit is set to the bit just after
12276 -- the last component of DS and CL.
12278 --------------------------
12279 -- Check_Component_List --
12280 --------------------------
12282 procedure Check_Component_List
12288 Compl
: constant Natural :=
12289 Natural (List_Length
(Component_Items
(CL
)) + List_Length
(DS
));
12291 Comps
: array (Natural range 0 .. Compl
) of Entity_Id
;
12292 -- Gather components (zero entry is for sort routine)
12294 Ncomps
: Natural := 0;
12295 -- Number of entries stored in Comps (starting at Comps (1))
12298 -- One component item or discriminant specification
12301 -- Starting bit for next component
12304 -- Component entity
12309 function Lt
(Op1
, Op2
: Natural) return Boolean;
12310 -- Compare routine for Sort
12312 procedure Move
(From
: Natural; To
: Natural);
12313 -- Move routine for Sort
12315 package Sorting
is new GNAT
.Heap_Sort_G
(Move
, Lt
);
12321 function Lt
(Op1
, Op2
: Natural) return Boolean is
12322 K1
: constant Boolean :=
12323 Known_Component_Bit_Offset
(Comps
(Op1
));
12324 K2
: constant Boolean :=
12325 Known_Component_Bit_Offset
(Comps
(Op2
));
12326 -- Record representation clauses can be incomplete, so the
12327 -- Component_Bit_Offsets can be unknown.
12331 return Component_Bit_Offset
(Comps
(Op1
))
12332 < Component_Bit_Offset
(Comps
(Op2
));
12345 procedure Move
(From
: Natural; To
: Natural) is
12347 Comps
(To
) := Comps
(From
);
12350 -- Start of processing for Check_Component_List
12353 -- Gather discriminants into Comp
12355 Citem
:= First
(DS
);
12356 while Present
(Citem
) loop
12357 if Nkind
(Citem
) = N_Discriminant_Specification
then
12359 Ent
: constant Entity_Id
:=
12360 Defining_Identifier
(Citem
);
12362 if Ekind
(Ent
) = E_Discriminant
then
12363 Ncomps
:= Ncomps
+ 1;
12364 Comps
(Ncomps
) := Ent
;
12372 -- Gather component entities into Comp
12374 Citem
:= First
(Component_Items
(CL
));
12375 while Present
(Citem
) loop
12376 if Nkind
(Citem
) = N_Component_Declaration
then
12377 Ncomps
:= Ncomps
+ 1;
12378 Comps
(Ncomps
) := Defining_Identifier
(Citem
);
12384 -- Now sort the component entities based on the first bit.
12385 -- Note we already know there are no overlapping components.
12387 Sorting
.Sort
(Ncomps
);
12389 -- Loop through entries checking for holes
12392 for J
in 1 .. Ncomps
loop
12394 pragma Annotate
(CodePeer
, Modified
, CEnt
);
12397 CBO
: constant Uint
:= Component_Bit_Offset
(CEnt
);
12400 -- Skip components with unknown offsets
12402 if Present
(CBO
) and then CBO
>= 0 then
12403 Error_Msg_Uint_1
:= CBO
- Nbit
;
12405 if Warn
and then Error_Msg_Uint_1
> 0 then
12407 ("?.h?^-bit gap before component&",
12408 Component_Name
(Component_Clause
(CEnt
)),
12412 Nbit
:= CBO
+ Esize
(CEnt
);
12417 -- Set Abit to just after the last nonvariant component
12421 -- Process variant parts recursively if present. Set Abit to the
12422 -- maximum for all variant parts.
12424 if Present
(Variant_Part
(CL
)) then
12426 Var_Start
: constant Uint
:= Nbit
;
12428 Variant
:= First
(Variants
(Variant_Part
(CL
)));
12429 while Present
(Variant
) loop
12430 Check_Component_List
12431 (No_List
, Component_List
(Variant
), Var_Start
, Nbit
);
12433 if Nbit
> Abit
then
12439 end Check_Component_List
;
12444 -- Starting bit for call to Check_Component_List. Zero for an
12445 -- untagged type. The size of the Tag for a nonderived tagged
12446 -- type. Parent size for a type extension.
12448 Record_Definition
: Node_Id
;
12449 -- Record_Definition containing Component_List to pass to
12450 -- Check_Component_List.
12452 -- Start of processing for Record_Hole_Check
12455 if Is_Tagged_Type
(Rectype
) then
12456 Sbit
:= UI_From_Int
(System_Address_Size
);
12461 After_Last
:= Uint_0
;
12463 if Nkind
(Decl
) = N_Full_Type_Declaration
then
12464 Record_Definition
:= Type_Definition
(Decl
);
12466 -- If we have a record extension, set Sbit to point after the last
12467 -- component of the parent type, by calling Record_Hole_Check
12470 if Nkind
(Record_Definition
) = N_Derived_Type_Definition
then
12471 Record_Definition
:= Record_Extension_Part
(Record_Definition
);
12472 Record_Hole_Check
(Underlying_Type
(Parent_Subtype
(Rectype
)),
12473 After_Last
=> Sbit
, Warn
=> False);
12476 if Nkind
(Record_Definition
) = N_Record_Definition
then
12477 Check_Component_List
12478 (Discriminant_Specifications
(Decl
),
12479 Component_List
(Record_Definition
),
12483 end Record_Hole_Check
;
12485 -- Start of processing for Check_Record_Representation_Clause
12489 Rectype
:= Entity
(Ident
);
12491 if Rectype
= Any_Type
then
12495 Rectype
:= Underlying_Type
(Rectype
);
12497 -- See if we have a fully repped derived tagged type
12500 PS
: constant Entity_Id
:= Parent_Subtype
(Rectype
);
12503 if Present
(PS
) and then Known_Static_RM_Size
(PS
) then
12504 Tagged_Parent
:= PS
;
12505 Parent_Last_Bit
:= RM_Size
(PS
) - 1;
12507 elsif Present
(PS
) and then Is_Fully_Repped_Tagged_Type
(PS
) then
12508 Tagged_Parent
:= PS
;
12510 -- Find maximum bit of any component of the parent type
12512 Parent_Last_Bit
:= UI_From_Int
(System_Address_Size
- 1);
12513 Pcomp
:= First_Component_Or_Discriminant
(Tagged_Parent
);
12514 while Present
(Pcomp
) loop
12515 if Present
(Component_Bit_Offset
(Pcomp
))
12516 and then Known_Static_Esize
(Pcomp
)
12521 Component_Bit_Offset
(Pcomp
) + Esize
(Pcomp
) - 1);
12524 Next_Component_Or_Discriminant
(Pcomp
);
12529 -- All done if no component clauses
12531 CC
:= First
(Component_Clauses
(N
));
12537 -- If a tag is present, then create a component clause that places it
12538 -- at the start of the record (otherwise gigi may place it after other
12539 -- fields that have rep clauses).
12541 Fent
:= First_Entity
(Rectype
);
12543 if Nkind
(Fent
) = N_Defining_Identifier
12544 and then Chars
(Fent
) = Name_uTag
12546 Set_Component_Bit_Offset
(Fent
, Uint_0
);
12547 Set_Normalized_Position
(Fent
, Uint_0
);
12548 Set_Normalized_First_Bit
(Fent
, Uint_0
);
12549 Set_Esize
(Fent
, UI_From_Int
(System_Address_Size
));
12551 Set_Component_Clause
(Fent
,
12552 Make_Component_Clause
(Loc
,
12553 Component_Name
=> Make_Identifier
(Loc
, Name_uTag
),
12555 Position
=> Make_Integer_Literal
(Loc
, Uint_0
),
12556 First_Bit
=> Make_Integer_Literal
(Loc
, Uint_0
),
12558 Make_Integer_Literal
(Loc
,
12559 UI_From_Int
(System_Address_Size
- 1))));
12561 Ccount
:= Ccount
+ 1;
12564 Max_Bit_So_Far
:= Uint_Minus_1
;
12565 Overlap_Check_Required
:= False;
12567 -- Process the component clauses
12569 while Present
(CC
) loop
12572 if Present
(Comp
) then
12573 Ccount
:= Ccount
+ 1;
12575 -- We need a full overlap check if record positions non-monotonic
12577 if Fbit
<= Max_Bit_So_Far
then
12578 Overlap_Check_Required
:= True;
12581 Max_Bit_So_Far
:= Lbit
;
12583 -- Check bit position out of range of specified size
12585 if Has_Size_Clause
(Rectype
)
12586 and then RM_Size
(Rectype
) <= Lbit
12588 Error_Msg_Uint_1
:= RM_Size
(Rectype
);
12589 Error_Msg_Uint_2
:= Lbit
+ 1;
12590 Error_Msg_N
("bit number out of range of specified "
12591 & "size (expected ^, got ^)",
12594 -- Check for overlap with tag or parent component
12597 if Is_Tagged_Type
(Rectype
)
12598 and then Fbit
< System_Address_Size
12601 ("component overlaps tag field of&",
12602 Component_Name
(CC
), Rectype
);
12603 Overlap_Detected
:= True;
12605 elsif Present
(Tagged_Parent
)
12606 and then Fbit
<= Parent_Last_Bit
12609 ("component overlaps parent field of&",
12610 Component_Name
(CC
), Rectype
);
12611 Overlap_Detected
:= True;
12614 if Hbit
< Lbit
then
12623 -- Now that we have processed all the component clauses, check for
12624 -- overlap. We have to leave this till last, since the components can
12625 -- appear in any arbitrary order in the representation clause.
12627 -- We do not need this check if all specified ranges were monotonic,
12628 -- as recorded by Overlap_Check_Required being False at this stage.
12630 -- This first section checks if there are any overlapping entries at
12631 -- all. It does this by sorting all entries and then seeing if there are
12632 -- any overlaps. If there are none, then that is decisive, but if there
12633 -- are overlaps, they may still be OK (they may result from fields in
12634 -- different variants).
12636 if Overlap_Check_Required
then
12637 Overlap_Check1
: declare
12639 OC_Fbit
: array (0 .. Ccount
) of Uint
;
12640 -- First-bit values for component clauses, the value is the offset
12641 -- of the first bit of the field from start of record. The zero
12642 -- entry is for use in sorting.
12644 OC_Lbit
: array (0 .. Ccount
) of Uint
;
12645 -- Last-bit values for component clauses, the value is the offset
12646 -- of the last bit of the field from start of record. The zero
12647 -- entry is for use in sorting.
12649 OC_Count
: Natural := 0;
12650 -- Count of entries in OC_Fbit and OC_Lbit
12652 function OC_Lt
(Op1
, Op2
: Natural) return Boolean;
12653 -- Compare routine for Sort
12655 procedure OC_Move
(From
: Natural; To
: Natural);
12656 -- Move routine for Sort
12658 package Sorting
is new GNAT
.Heap_Sort_G
(OC_Move
, OC_Lt
);
12664 function OC_Lt
(Op1
, Op2
: Natural) return Boolean is
12666 return OC_Fbit
(Op1
) < OC_Fbit
(Op2
);
12673 procedure OC_Move
(From
: Natural; To
: Natural) is
12675 OC_Fbit
(To
) := OC_Fbit
(From
);
12676 OC_Lbit
(To
) := OC_Lbit
(From
);
12679 -- Start of processing for Overlap_Check
12682 CC
:= First
(Component_Clauses
(N
));
12683 while Present
(CC
) loop
12685 -- Exclude component clause already marked in error
12687 if not Error_Posted
(CC
) then
12690 if Present
(Comp
) then
12691 OC_Count
:= OC_Count
+ 1;
12692 OC_Fbit
(OC_Count
) := Fbit
;
12693 OC_Lbit
(OC_Count
) := Lbit
;
12700 Sorting
.Sort
(OC_Count
);
12702 Overlap_Check_Required
:= False;
12703 for J
in 1 .. OC_Count
- 1 loop
12704 if OC_Lbit
(J
) >= OC_Fbit
(J
+ 1) then
12705 Overlap_Check_Required
:= True;
12709 end Overlap_Check1
;
12712 -- If Overlap_Check_Required is still True, then we have to do the full
12713 -- scale overlap check, since we have at least two fields that do
12714 -- overlap, and we need to know if that is OK since they are in
12715 -- different variant, or whether we have a definite problem.
12717 if Overlap_Check_Required
then
12718 Overlap_Check2
: declare
12719 C1_Ent
, C2_Ent
: Entity_Id
;
12720 -- Entities of components being checked for overlap
12723 -- Component_List node whose Component_Items are being checked
12726 -- Component declaration for component being checked
12729 C1_Ent
:= First_Entity
(Base_Type
(Rectype
));
12731 -- Loop through all components in record. For each component check
12732 -- for overlap with any of the preceding elements on the component
12733 -- list containing the component and also, if the component is in
12734 -- a variant, check against components outside the case structure.
12735 -- This latter test is repeated recursively up the variant tree.
12737 Main_Component_Loop
: while Present
(C1_Ent
) loop
12738 if Ekind
(C1_Ent
) not in E_Component | E_Discriminant
then
12739 goto Continue_Main_Component_Loop
;
12742 -- Skip overlap check if entity has no declaration node. This
12743 -- happens with discriminants in constrained derived types.
12744 -- Possibly we are missing some checks as a result, but that
12745 -- does not seem terribly serious.
12747 if No
(Declaration_Node
(C1_Ent
)) then
12748 goto Continue_Main_Component_Loop
;
12751 Clist
:= Parent
(List_Containing
(Declaration_Node
(C1_Ent
)));
12753 -- Loop through component lists that need checking. Check the
12754 -- current component list and all lists in variants above us.
12756 Component_List_Loop
: loop
12758 -- If derived type definition, go to full declaration
12759 -- If at outer level, check discriminants if there are any.
12761 if Nkind
(Clist
) = N_Derived_Type_Definition
then
12762 Clist
:= Parent
(Clist
);
12765 -- Outer level of record definition, check discriminants
12766 -- but be careful not to flag a non-stored discriminant
12767 -- and the stored discriminant it renames as overlapping.
12769 if Nkind
(Clist
) in N_Full_Type_Declaration
12770 | N_Private_Type_Declaration
12772 if Has_Discriminants
(Defining_Identifier
(Clist
)) then
12774 First_Discriminant
(Defining_Identifier
(Clist
));
12775 while Present
(C2_Ent
) loop
12777 Original_Record_Component
(C1_Ent
) =
12778 Original_Record_Component
(C2_Ent
);
12779 Check_Component_Overlap
(C1_Ent
, C2_Ent
);
12780 Next_Discriminant
(C2_Ent
);
12784 -- Record extension case
12786 elsif Nkind
(Clist
) = N_Derived_Type_Definition
then
12789 -- Otherwise check one component list
12792 Citem
:= First
(Component_Items
(Clist
));
12793 while Present
(Citem
) loop
12794 if Nkind
(Citem
) = N_Component_Declaration
then
12795 C2_Ent
:= Defining_Identifier
(Citem
);
12796 exit when C1_Ent
= C2_Ent
;
12797 Check_Component_Overlap
(C1_Ent
, C2_Ent
);
12804 -- Check for variants above us (the parent of the Clist can
12805 -- be a variant, in which case its parent is a variant part,
12806 -- and the parent of the variant part is a component list
12807 -- whose components must all be checked against the current
12808 -- component for overlap).
12810 if Nkind
(Parent
(Clist
)) = N_Variant
then
12811 Clist
:= Parent
(Parent
(Parent
(Clist
)));
12813 -- Check for possible discriminant part in record, this
12814 -- is treated essentially as another level in the
12815 -- recursion. For this case the parent of the component
12816 -- list is the record definition, and its parent is the
12817 -- full type declaration containing the discriminant
12820 elsif Nkind
(Parent
(Clist
)) = N_Record_Definition
then
12821 Clist
:= Parent
(Parent
((Clist
)));
12823 -- If neither of these two cases, we are at the top of
12827 exit Component_List_Loop
;
12829 end loop Component_List_Loop
;
12831 <<Continue_Main_Component_Loop
>>
12832 Next_Entity
(C1_Ent
);
12834 end loop Main_Component_Loop
;
12835 end Overlap_Check2
;
12838 -- Skip the following warnings if overlap was detected; programmer
12839 -- should fix the errors first. Also skip the warnings for types in
12840 -- generics, because their representation information is not fully
12843 if not Overlap_Detected
and then not In_Generic_Scope
(Rectype
) then
12844 -- Check for record holes (gaps)
12846 if Warn_On_Record_Holes
then
12850 Record_Hole_Check
(Rectype
, After_Last
=> Ignore
, Warn
=> True);
12854 -- Check for out-of-order component clauses
12856 if Warn_On_Component_Order
then
12857 Component_Order_Check
(Rectype
);
12861 -- For records that have component clauses for all components, and whose
12862 -- size is less than or equal to 32, and which can be fully packed, we
12863 -- need to know the size in the front end to activate possible packed
12864 -- array processing where the component type is a record.
12866 -- At this stage Hbit + 1 represents the first unused bit from all the
12867 -- component clauses processed, so if the component clauses are
12868 -- complete, then this is the length of the record.
12870 -- For records longer than System.Storage_Unit, and for those where not
12871 -- all components have component clauses, the back end determines the
12872 -- length (it may for example be appropriate to round up the size
12873 -- to some convenient boundary, based on alignment considerations, etc).
12875 if not Known_RM_Size
(Rectype
)
12876 and then Hbit
+ 1 <= 32
12877 and then not Strict_Alignment
(Rectype
)
12880 -- Nothing to do if at least one component has no component clause
12882 Comp
:= First_Component_Or_Discriminant
(Rectype
);
12883 while Present
(Comp
) loop
12884 exit when No
(Component_Clause
(Comp
));
12885 Next_Component_Or_Discriminant
(Comp
);
12888 -- If we fall out of loop, all components have component clauses
12889 -- and so we can set the size to the maximum value.
12892 Set_RM_Size
(Rectype
, Hbit
+ 1);
12895 end Check_Record_Representation_Clause
;
12901 procedure Check_Size
12905 Biased
: out Boolean)
12907 procedure Size_Too_Small_Error
(Min_Siz
: Uint
);
12908 -- Emit an error concerning illegal size Siz. Min_Siz denotes the
12911 --------------------------
12912 -- Size_Too_Small_Error --
12913 --------------------------
12915 procedure Size_Too_Small_Error
(Min_Siz
: Uint
) is
12917 Error_Msg_Uint_1
:= Min_Siz
;
12918 Error_Msg_NE
(Size_Too_Small_Message
, N
, T
);
12919 end Size_Too_Small_Error
;
12923 UT
: constant Entity_Id
:= Underlying_Type
(T
);
12926 -- Start of processing for Check_Size
12931 -- Reject patently improper size values
12933 if Is_Elementary_Type
(T
)
12934 and then Siz
> Int
'Last
12936 Error_Msg_N
("Size value too large for elementary type", N
);
12938 if Nkind
(Original_Node
(N
)) = N_Op_Expon
then
12940 ("\maybe '* was meant, rather than '*'*", Original_Node
(N
));
12944 -- Dismiss generic types
12946 if Is_Generic_Type
(T
)
12948 Is_Generic_Type
(UT
)
12950 Is_Generic_Type
(Root_Type
(UT
))
12954 -- Guard against previous errors
12956 elsif No
(UT
) or else UT
= Any_Type
then
12957 Check_Error_Detected
;
12960 -- Check case of bit packed array
12962 elsif Is_Array_Type
(UT
)
12963 and then Known_Static_Component_Size
(UT
)
12964 and then Is_Bit_Packed_Array
(UT
)
12972 Asiz
:= Component_Size
(UT
);
12973 Indx
:= First_Index
(UT
);
12975 Ityp
:= Etype
(Indx
);
12977 -- If non-static bound, then we are not in the business of
12978 -- trying to check the length, and indeed an error will be
12979 -- issued elsewhere, since sizes of non-static array types
12980 -- cannot be set implicitly or explicitly.
12982 if not Is_OK_Static_Subtype
(Ityp
) then
12986 -- Otherwise accumulate next dimension
12988 Asiz
:= Asiz
* (Expr_Value
(Type_High_Bound
(Ityp
)) -
12989 Expr_Value
(Type_Low_Bound
(Ityp
)) +
12993 exit when No
(Indx
);
12996 if Asiz
<= Siz
then
13000 Size_Too_Small_Error
(Asiz
);
13004 -- All other composite types are ignored
13006 elsif Is_Composite_Type
(UT
) then
13009 -- For fixed-point types, don't check minimum if type is not frozen,
13010 -- since we don't know all the characteristics of the type that can
13011 -- affect the size (e.g. a specified small) till freeze time.
13013 elsif Is_Fixed_Point_Type
(UT
) and then not Is_Frozen
(UT
) then
13016 -- Cases for which a minimum check is required
13019 -- Ignore if specified size is correct for the type
13021 if Known_Esize
(UT
) and then Siz
= Esize
(UT
) then
13025 -- Otherwise get minimum size
13027 M
:= UI_From_Int
(Minimum_Size
(UT
));
13031 -- Size is less than minimum size, but one possibility remains
13032 -- that we can manage with the new size if we bias the type.
13034 M
:= UI_From_Int
(Minimum_Size
(UT
, Biased
=> True));
13037 Size_Too_Small_Error
(M
);
13045 --------------------------
13046 -- Freeze_Entity_Checks --
13047 --------------------------
13049 procedure Freeze_Entity_Checks
(N
: Node_Id
) is
13050 procedure Hide_Non_Overridden_Subprograms
(Typ
: Entity_Id
);
13051 -- Inspect the primitive operations of type Typ and hide all pairs of
13052 -- implicitly declared non-overridden non-fully conformant homographs
13053 -- (Ada RM 8.3 12.3/2).
13055 -------------------------------------
13056 -- Hide_Non_Overridden_Subprograms --
13057 -------------------------------------
13059 procedure Hide_Non_Overridden_Subprograms
(Typ
: Entity_Id
) is
13060 procedure Hide_Matching_Homographs
13061 (Subp_Id
: Entity_Id
;
13062 Start_Elmt
: Elmt_Id
);
13063 -- Inspect a list of primitive operations starting with Start_Elmt
13064 -- and find matching implicitly declared non-overridden non-fully
13065 -- conformant homographs of Subp_Id. If found, all matches along
13066 -- with Subp_Id are hidden from all visibility.
13068 function Is_Non_Overridden_Or_Null_Procedure
13069 (Subp_Id
: Entity_Id
) return Boolean;
13070 -- Determine whether subprogram Subp_Id is implicitly declared non-
13071 -- overridden subprogram or an implicitly declared null procedure.
13073 ------------------------------
13074 -- Hide_Matching_Homographs --
13075 ------------------------------
13077 procedure Hide_Matching_Homographs
13078 (Subp_Id
: Entity_Id
;
13079 Start_Elmt
: Elmt_Id
)
13082 Prim_Elmt
: Elmt_Id
;
13085 Prim_Elmt
:= Start_Elmt
;
13086 while Present
(Prim_Elmt
) loop
13087 Prim
:= Node
(Prim_Elmt
);
13089 -- The current primitive is implicitly declared non-overridden
13090 -- non-fully conformant homograph of Subp_Id. Both subprograms
13091 -- must be hidden from visibility.
13093 if Chars
(Prim
) = Chars
(Subp_Id
)
13094 and then Is_Non_Overridden_Or_Null_Procedure
(Prim
)
13095 and then not Fully_Conformant
(Prim
, Subp_Id
)
13097 Set_Is_Hidden_Non_Overridden_Subpgm
(Prim
);
13098 Set_Is_Immediately_Visible
(Prim
, False);
13099 Set_Is_Potentially_Use_Visible
(Prim
, False);
13101 Set_Is_Hidden_Non_Overridden_Subpgm
(Subp_Id
);
13102 Set_Is_Immediately_Visible
(Subp_Id
, False);
13103 Set_Is_Potentially_Use_Visible
(Subp_Id
, False);
13106 Next_Elmt
(Prim_Elmt
);
13108 end Hide_Matching_Homographs
;
13110 -----------------------------------------
13111 -- Is_Non_Overridden_Or_Null_Procedure --
13112 -----------------------------------------
13114 function Is_Non_Overridden_Or_Null_Procedure
13115 (Subp_Id
: Entity_Id
) return Boolean
13117 Alias_Id
: Entity_Id
;
13120 -- The subprogram is inherited (implicitly declared), it does not
13121 -- override and does not cover a primitive of an interface.
13123 if Ekind
(Subp_Id
) in E_Function | E_Procedure
13124 and then Present
(Alias
(Subp_Id
))
13125 and then No
(Interface_Alias
(Subp_Id
))
13126 and then No
(Overridden_Operation
(Subp_Id
))
13128 Alias_Id
:= Alias
(Subp_Id
);
13130 if Requires_Overriding
(Alias_Id
) then
13133 elsif Nkind
(Parent
(Alias_Id
)) = N_Procedure_Specification
13134 and then Null_Present
(Parent
(Alias_Id
))
13141 end Is_Non_Overridden_Or_Null_Procedure
;
13145 Prim_Ops
: constant Elist_Id
:= Direct_Primitive_Operations
(Typ
);
13147 Prim_Elmt
: Elmt_Id
;
13149 -- Start of processing for Hide_Non_Overridden_Subprograms
13152 -- Inspect the list of primitives looking for non-overridden
13155 if Present
(Prim_Ops
) then
13156 Prim_Elmt
:= First_Elmt
(Prim_Ops
);
13157 while Present
(Prim_Elmt
) loop
13158 Prim
:= Node
(Prim_Elmt
);
13159 Next_Elmt
(Prim_Elmt
);
13161 if Is_Non_Overridden_Or_Null_Procedure
(Prim
) then
13162 Hide_Matching_Homographs
13164 Start_Elmt
=> Prim_Elmt
);
13168 end Hide_Non_Overridden_Subprograms
;
13172 E
: constant Entity_Id
:= Entity
(N
);
13174 Nongeneric_Case
: constant Boolean := Nkind
(N
) = N_Freeze_Entity
;
13175 -- True in nongeneric case. Some of the processing here is skipped
13176 -- for the generic case since it is not needed. Basically in the
13177 -- generic case, we only need to do stuff that might generate error
13178 -- messages or warnings.
13180 -- Start of processing for Freeze_Entity_Checks
13183 -- Remember that we are processing a freezing entity. Required to
13184 -- ensure correct decoration of internal entities associated with
13185 -- interfaces (see New_Overloaded_Entity).
13187 Inside_Freezing_Actions
:= Inside_Freezing_Actions
+ 1;
13189 -- For tagged types covering interfaces add internal entities that link
13190 -- the primitives of the interfaces with the primitives that cover them.
13191 -- Note: These entities were originally generated only when generating
13192 -- code because their main purpose was to provide support to initialize
13193 -- the secondary dispatch tables. They are also used to locate
13194 -- primitives covering interfaces when processing generics (see
13195 -- Derive_Subprograms).
13197 -- This is not needed in the generic case
13199 if Ada_Version
>= Ada_2005
13200 and then Nongeneric_Case
13201 and then Ekind
(E
) = E_Record_Type
13202 and then Is_Tagged_Type
(E
)
13203 and then not Is_Interface
(E
)
13204 and then Has_Interfaces
(E
)
13206 -- This would be a good common place to call the routine that checks
13207 -- overriding of interface primitives (and thus factorize calls to
13208 -- Check_Abstract_Overriding located at different contexts in the
13209 -- compiler). However, this is not possible because it causes
13210 -- spurious errors in case of late overriding.
13212 Add_Internal_Interface_Entities
(E
);
13215 -- After all forms of overriding have been resolved, a tagged type may
13216 -- be left with a set of implicitly declared and possibly erroneous
13217 -- abstract subprograms, null procedures and subprograms that require
13218 -- overriding. If this set contains fully conformant homographs, then
13219 -- one is chosen arbitrarily (already done during resolution), otherwise
13220 -- all remaining non-fully conformant homographs are hidden from
13221 -- visibility (Ada RM 8.3 12.3/2).
13223 if Is_Tagged_Type
(E
) then
13224 Hide_Non_Overridden_Subprograms
(E
);
13229 if Ekind
(E
) = E_Record_Type
13230 and then Is_CPP_Class
(E
)
13231 and then Is_Tagged_Type
(E
)
13232 and then Tagged_Type_Expansion
13234 if CPP_Num_Prims
(E
) = 0 then
13236 -- If the CPP type has user defined components then it must import
13237 -- primitives from C++. This is required because if the C++ class
13238 -- has no primitives then the C++ compiler does not added the _tag
13239 -- component to the type.
13241 if First_Entity
(E
) /= Last_Entity
(E
) then
13243 ("'C'P'P type must import at least one primitive from C++??",
13248 -- Check that all its primitives are abstract or imported from C++.
13249 -- Check also availability of the C++ constructor.
13252 Has_Constructors
: constant Boolean := Has_CPP_Constructors
(E
);
13254 Error_Reported
: Boolean := False;
13258 Elmt
:= First_Elmt
(Primitive_Operations
(E
));
13259 while Present
(Elmt
) loop
13260 Prim
:= Node
(Elmt
);
13262 if Comes_From_Source
(Prim
) then
13263 if Is_Abstract_Subprogram
(Prim
) then
13266 elsif not Is_Imported
(Prim
)
13267 or else Convention
(Prim
) /= Convention_CPP
13270 ("primitives of 'C'P'P types must be imported from C++ "
13271 & "or abstract??", Prim
);
13273 elsif not Has_Constructors
13274 and then not Error_Reported
13276 Error_Msg_Name_1
:= Chars
(E
);
13278 ("??'C'P'P constructor required for type %", Prim
);
13279 Error_Reported
:= True;
13288 -- Check Ada derivation of CPP type
13290 if Expander_Active
-- why? losing errors in -gnatc mode???
13291 and then Present
(Etype
(E
)) -- defend against errors
13292 and then Tagged_Type_Expansion
13293 and then Ekind
(E
) = E_Record_Type
13294 and then Etype
(E
) /= E
13295 and then Is_CPP_Class
(Etype
(E
))
13296 and then CPP_Num_Prims
(Etype
(E
)) > 0
13297 and then not Is_CPP_Class
(E
)
13298 and then not Has_CPP_Constructors
(Etype
(E
))
13300 -- If the parent has C++ primitives but it has no constructor then
13301 -- check that all the primitives are overridden in this derivation;
13302 -- otherwise the constructor of the parent is needed to build the
13310 Elmt
:= First_Elmt
(Primitive_Operations
(E
));
13311 while Present
(Elmt
) loop
13312 Prim
:= Node
(Elmt
);
13314 if not Is_Abstract_Subprogram
(Prim
)
13315 and then No
(Interface_Alias
(Prim
))
13316 and then Find_Dispatching_Type
(Ultimate_Alias
(Prim
)) /= E
13318 Error_Msg_Name_1
:= Chars
(Etype
(E
));
13320 ("'C'P'P constructor required for parent type %", E
);
13329 Inside_Freezing_Actions
:= Inside_Freezing_Actions
- 1;
13331 -- For a record type, deal with variant parts. This has to be delayed to
13332 -- this point, because of the issue of statically predicated subtypes,
13333 -- which we have to ensure are frozen before checking choices, since we
13334 -- need to have the static choice list set.
13336 if Is_Record_Type
(E
) then
13337 Check_Variant_Part
: declare
13338 D
: constant Node_Id
:= Declaration_Node
(E
);
13343 Others_Present
: Boolean;
13344 pragma Warnings
(Off
, Others_Present
);
13345 -- Indicates others present, not used in this case
13347 procedure Non_Static_Choice_Error
(Choice
: Node_Id
);
13348 -- Error routine invoked by the generic instantiation below when
13349 -- the variant part has a non static choice.
13351 procedure Process_Declarations
(Variant
: Node_Id
);
13352 -- Processes declarations associated with a variant. We analyzed
13353 -- the declarations earlier (in Sem_Ch3.Analyze_Variant_Part),
13354 -- but we still need the recursive call to Check_Choices for any
13355 -- nested variant to get its choices properly processed. This is
13356 -- also where we expand out the choices if expansion is active.
13358 package Variant_Choices_Processing
is new
13359 Generic_Check_Choices
13360 (Process_Empty_Choice
=> No_OP
,
13361 Process_Non_Static_Choice
=> Non_Static_Choice_Error
,
13362 Process_Associated_Node
=> Process_Declarations
);
13363 use Variant_Choices_Processing
;
13365 -----------------------------
13366 -- Non_Static_Choice_Error --
13367 -----------------------------
13369 procedure Non_Static_Choice_Error
(Choice
: Node_Id
) is
13371 Flag_Non_Static_Expr
13372 ("choice given in variant part is not static!", Choice
);
13373 end Non_Static_Choice_Error
;
13375 --------------------------
13376 -- Process_Declarations --
13377 --------------------------
13379 procedure Process_Declarations
(Variant
: Node_Id
) is
13380 CL
: constant Node_Id
:= Component_List
(Variant
);
13384 -- Check for static predicate present in this variant
13386 if Has_SP_Choice
(Variant
) then
13388 -- Here we expand. You might expect to find this call in
13389 -- Expand_N_Variant_Part, but that is called when we first
13390 -- see the variant part, and we cannot do this expansion
13391 -- earlier than the freeze point, since for statically
13392 -- predicated subtypes, the predicate is not known till
13393 -- the freeze point.
13395 -- Furthermore, we do this expansion even if the expander
13396 -- is not active, because other semantic processing, e.g.
13397 -- for aggregates, requires the expanded list of choices.
13399 -- If the expander is not active, then we can't just clobber
13400 -- the list since it would invalidate the tree.
13401 -- So we have to rewrite the variant part with a Rewrite
13402 -- call that replaces it with a copy and clobber the copy.
13404 if not Expander_Active
then
13406 NewV
: constant Node_Id
:= New_Copy
(Variant
);
13408 Set_Discrete_Choices
13409 (NewV
, New_Copy_List
(Discrete_Choices
(Variant
)));
13410 Rewrite
(Variant
, NewV
);
13414 Expand_Static_Predicates_In_Choices
(Variant
);
13417 -- We don't need to worry about the declarations in the variant
13418 -- (since they were analyzed by Analyze_Choices when we first
13419 -- encountered the variant), but we do need to take care of
13420 -- expansion of any nested variants.
13422 if not Null_Present
(CL
) then
13423 VP
:= Variant_Part
(CL
);
13425 if Present
(VP
) then
13427 (VP
, Variants
(VP
), Etype
(Name
(VP
)), Others_Present
);
13430 end Process_Declarations
;
13432 -- Start of processing for Check_Variant_Part
13435 -- Find component list
13439 if Nkind
(D
) = N_Full_Type_Declaration
then
13440 T
:= Type_Definition
(D
);
13442 if Nkind
(T
) = N_Record_Definition
then
13443 C
:= Component_List
(T
);
13445 elsif Nkind
(T
) = N_Derived_Type_Definition
13446 and then Present
(Record_Extension_Part
(T
))
13448 C
:= Component_List
(Record_Extension_Part
(T
));
13452 -- Case of variant part present
13454 if Present
(C
) and then Present
(Variant_Part
(C
)) then
13455 VP
:= Variant_Part
(C
);
13460 (VP
, Variants
(VP
), Etype
(Name
(VP
)), Others_Present
);
13462 -- If the last variant does not contain the Others choice,
13463 -- replace it with an N_Others_Choice node since Gigi always
13464 -- wants an Others. Note that we do not bother to call Analyze
13465 -- on the modified variant part, since its only effect would be
13466 -- to compute the Others_Discrete_Choices node laboriously, and
13467 -- of course we already know the list of choices corresponding
13468 -- to the others choice (it's the list we're replacing).
13470 -- We only want to do this if the expander is active, since
13471 -- we do not want to clobber the tree.
13473 if Expander_Active
then
13475 Last_Var
: constant Node_Id
:=
13476 Last_Non_Pragma
(Variants
(VP
));
13478 Others_Node
: Node_Id
;
13481 if Nkind
(First
(Discrete_Choices
(Last_Var
))) /=
13484 Others_Node
:= Make_Others_Choice
(Sloc
(Last_Var
));
13485 Set_Others_Discrete_Choices
13486 (Others_Node
, Discrete_Choices
(Last_Var
));
13487 Set_Discrete_Choices
13488 (Last_Var
, New_List
(Others_Node
));
13493 end Check_Variant_Part
;
13496 -- If we have a type with predicates, build predicate function. This is
13497 -- not needed in the generic case, nor within e.g. TSS subprograms and
13498 -- other predefined primitives. For a derived type, ensure that the
13499 -- parent type is already frozen so that its predicate function has been
13500 -- constructed already. This is necessary if the parent is declared
13501 -- in a nested package and its own freeze point has not been reached.
13504 and then Nongeneric_Case
13505 and then Has_Predicates
(E
)
13506 and then Predicate_Check_In_Scope
(N
)
13509 Atyp
: constant Entity_Id
:= Nearest_Ancestor
(E
);
13513 and then Has_Predicates
(Atyp
)
13514 and then not Is_Frozen
(Atyp
)
13516 Freeze_Before
(N
, Atyp
);
13520 -- Before we build a predicate function, ensure that discriminant
13521 -- checking functions are available. The predicate function might
13522 -- need to call these functions if the predicate references any
13523 -- components declared in a variant part.
13525 if Ekind
(E
) = E_Record_Type
and then Has_Discriminants
(E
) then
13526 Build_Or_Copy_Discr_Checking_Funcs
(Parent
(E
));
13529 Build_Predicate_Function
(E
, N
);
13532 -- If type has delayed aspects, this is where we do the preanalysis at
13533 -- the freeze point, as part of the consistent visibility check. Note
13534 -- that this must be done after calling Build_Predicate_Function or
13535 -- Build_Invariant_Procedure since these subprograms fix occurrences of
13536 -- the subtype name in the saved expression so that they will not cause
13537 -- trouble in the preanalysis.
13539 -- This is also not needed in the generic case
13542 and then Has_Delayed_Aspects
(E
)
13543 and then Scope
(E
) = Current_Scope
13549 -- Look for aspect specification entries for this entity
13551 Ritem
:= First_Rep_Item
(E
);
13552 while Present
(Ritem
) loop
13553 if Nkind
(Ritem
) = N_Aspect_Specification
13554 and then Entity
(Ritem
) = E
13555 and then Is_Delayed_Aspect
(Ritem
)
13557 if Get_Aspect_Id
(Ritem
) in Aspect_CPU
13558 | Aspect_Dynamic_Predicate
13559 | Aspect_Ghost_Predicate
13561 | Aspect_Static_Predicate
13564 -- Retrieve the visibility to components and discriminants
13565 -- in order to properly analyze the aspects.
13568 Check_Aspect_At_Freeze_Point
(Ritem
);
13570 -- In the case of predicate aspects, there will be
13571 -- a corresponding Predicate pragma associated with
13572 -- the aspect, and the expression of the pragma also
13573 -- needs to be analyzed at this point, to ensure that
13574 -- Save_Global_References will capture global refs in
13575 -- expressions that occur in generic bodies, for proper
13576 -- later resolution of the pragma in instantiations.
13579 and then Inside_A_Generic
13580 and then Has_Predicates
(E
)
13581 and then Present
(Aspect_Rep_Item
(Ritem
))
13584 Pragma_Args
: constant List_Id
:=
13585 Pragma_Argument_Associations
13586 (Aspect_Rep_Item
(Ritem
));
13587 Pragma_Expr
: constant Node_Id
:=
13588 Expression
(Next
(First
(Pragma_Args
)));
13590 if Present
(Pragma_Expr
) then
13591 Analyze_And_Resolve
13592 (Pragma_Expr
, Standard_Boolean
);
13600 Check_Aspect_At_Freeze_Point
(Ritem
);
13603 -- A pragma Predicate should be checked like one of the
13604 -- corresponding aspects, wrt possible misuse of ghost
13607 elsif Nkind
(Ritem
) = N_Pragma
13608 and then No
(Corresponding_Aspect
(Ritem
))
13610 Get_Pragma_Id
(Pragma_Name
(Ritem
)) = Pragma_Predicate
13612 -- Retrieve the visibility to components and discriminants
13613 -- in order to properly analyze the pragma.
13616 Arg
: constant Node_Id
:=
13617 Next
(First
(Pragma_Argument_Associations
(Ritem
)));
13620 Preanalyze_Spec_Expression
13621 (Expression
(Arg
), Standard_Boolean
);
13626 Next_Rep_Item
(Ritem
);
13631 if not In_Generic_Scope
(E
)
13632 and then Ekind
(E
) = E_Record_Type
13633 and then Is_Tagged_Type
(E
)
13635 Process_Class_Conditions_At_Freeze_Point
(E
);
13637 end Freeze_Entity_Checks
;
13639 -------------------------
13640 -- Get_Alignment_Value --
13641 -------------------------
13643 function Get_Alignment_Value
(Expr
: Node_Id
) return Uint
is
13644 Align
: constant Uint
:= Static_Integer
(Expr
);
13650 elsif Align
< 0 then
13651 Error_Msg_N
("alignment value must be positive", Expr
);
13654 -- If Alignment is specified to be 0, we treat it the same as 1
13656 elsif Align
= 0 then
13660 for J
in Int
range 0 .. 64 loop
13662 M
: constant Uint
:= Uint_2
** J
;
13665 exit when M
= Align
;
13668 Error_Msg_N
("alignment value must be power of 2", Expr
);
13676 end Get_Alignment_Value
;
13678 -----------------------------------
13679 -- Has_Compatible_Representation --
13680 -----------------------------------
13682 function Has_Compatible_Representation
13683 (Target_Typ
, Operand_Typ
: Entity_Id
) return Boolean
13685 -- The subtype-specific representation attributes (Size and Alignment)
13686 -- do not affect representation from the point of view of this function.
13688 T1
: constant Entity_Id
:= Implementation_Base_Type
(Target_Typ
);
13689 T2
: constant Entity_Id
:= Implementation_Base_Type
(Operand_Typ
);
13692 -- Return true immediately for the same base type
13697 -- Tagged types always have the same representation, because it is not
13698 -- possible to specify different representations for common fields.
13700 elsif Is_Tagged_Type
(T1
) then
13703 -- Representations are definitely different if conventions differ
13705 elsif Convention
(T1
) /= Convention
(T2
) then
13708 -- Representations are different if component alignments or scalar
13709 -- storage orders differ.
13711 elsif (Is_Record_Type
(T1
) or else Is_Array_Type
(T1
))
13713 (Is_Record_Type
(T2
) or else Is_Array_Type
(T2
))
13714 and then (Component_Alignment
(T1
) /= Component_Alignment
(T2
)
13716 Reverse_Storage_Order
(T1
) /= Reverse_Storage_Order
(T2
))
13721 -- For arrays, the only real issue is component size. If we know the
13722 -- component size for both arrays, and it is the same, then that's
13723 -- good enough to know we don't have a change of representation.
13725 if Is_Array_Type
(T1
) then
13727 -- In a view conversion, if the target type is an array type having
13728 -- aliased components and the operand type is an array type having
13729 -- unaliased components, then a new object is created (4.6(58.3/4)).
13731 if Has_Aliased_Components
(T1
)
13732 and then not Has_Aliased_Components
(T2
)
13737 if Known_Component_Size
(T1
)
13738 and then Known_Component_Size
(T2
)
13739 and then Component_Size
(T1
) = Component_Size
(T2
)
13744 -- For records, representations are different if reordering differs
13746 elsif Is_Record_Type
(T1
)
13747 and then Is_Record_Type
(T2
)
13748 and then No_Reordering
(T1
) /= No_Reordering
(T2
)
13753 -- Types definitely have same representation if neither has non-standard
13754 -- representation since default representations are always consistent.
13755 -- If only one has non-standard representation, and the other does not,
13756 -- then we consider that they do not have the same representation. They
13757 -- might, but there is no way of telling early enough.
13759 if Has_Non_Standard_Rep
(T1
) then
13760 if not Has_Non_Standard_Rep
(T2
) then
13764 return not Has_Non_Standard_Rep
(T2
);
13767 -- Here the two types both have non-standard representation, and we need
13768 -- to determine if they have the same non-standard representation.
13770 -- For arrays, we simply need to test if the component sizes are the
13771 -- same. Pragma Pack is reflected in modified component sizes, so this
13772 -- check also deals with pragma Pack.
13774 if Is_Array_Type
(T1
) then
13775 return Component_Size
(T1
) = Component_Size
(T2
);
13777 -- Case of record types
13779 elsif Is_Record_Type
(T1
) then
13781 -- Packed status must conform
13783 if Is_Packed
(T1
) /= Is_Packed
(T2
) then
13786 -- If the operand type is derived from the target type and no clause
13787 -- has been given after the derivation, then the representations are
13788 -- the same since the derived type inherits that of the parent type.
13790 elsif Is_Derived_Type
(T2
)
13791 and then Etype
(T2
) = T1
13792 and then not Has_Record_Rep_Clause
(T2
)
13796 -- Otherwise we must check components. Typ2 maybe a constrained
13797 -- subtype with fewer components, so we compare the components
13798 -- of the base types.
13801 Record_Case
: declare
13802 CD1
, CD2
: Entity_Id
;
13804 function Same_Rep
return Boolean;
13805 -- CD1 and CD2 are either components or discriminants. This
13806 -- function tests whether they have the same representation.
13812 function Same_Rep
return Boolean is
13814 if No
(Component_Clause
(CD1
)) then
13815 return No
(Component_Clause
(CD2
));
13817 -- Note: at this point, component clauses have been
13818 -- normalized to the default bit order, so that the
13819 -- comparison of Component_Bit_Offsets is meaningful.
13822 Present
(Component_Clause
(CD2
))
13824 Component_Bit_Offset
(CD1
) = Component_Bit_Offset
(CD2
)
13826 Esize
(CD1
) = Esize
(CD2
);
13830 -- Start of processing for Record_Case
13833 if Has_Discriminants
(T1
) then
13835 -- The number of discriminants may be different if the
13836 -- derived type has fewer (constrained by values). The
13837 -- invisible discriminants retain the representation of
13838 -- the original, so the discrepancy does not per se
13839 -- indicate a different representation.
13841 CD1
:= First_Discriminant
(T1
);
13842 CD2
:= First_Discriminant
(T2
);
13843 while Present
(CD1
) and then Present
(CD2
) loop
13844 if not Same_Rep
then
13847 Next_Discriminant
(CD1
);
13848 Next_Discriminant
(CD2
);
13853 CD1
:= First_Component
(Underlying_Type
(Base_Type
(T1
)));
13854 CD2
:= First_Component
(Underlying_Type
(Base_Type
(T2
)));
13855 while Present
(CD1
) loop
13856 if not Same_Rep
then
13859 Next_Component
(CD1
);
13860 Next_Component
(CD2
);
13868 -- For enumeration types, we must check each literal to see if the
13869 -- representation is the same. Note that we do not permit enumeration
13870 -- representation clauses for Character and Wide_Character, so these
13871 -- cases were already dealt with.
13873 elsif Is_Enumeration_Type
(T1
) then
13874 Enumeration_Case
: declare
13875 L1
, L2
: Entity_Id
;
13878 L1
:= First_Literal
(T1
);
13879 L2
:= First_Literal
(T2
);
13880 while Present
(L1
) loop
13881 if Enumeration_Rep
(L1
) /= Enumeration_Rep
(L2
) then
13890 end Enumeration_Case
;
13892 -- Any other types have the same representation for these purposes
13897 end Has_Compatible_Representation
;
13899 -------------------------------------
13900 -- Inherit_Aspects_At_Freeze_Point --
13901 -------------------------------------
13903 procedure Inherit_Aspects_At_Freeze_Point
(Typ
: Entity_Id
) is
13904 function Get_Inherited_Rep_Item
13906 Nam
: Name_Id
) return Node_Id
;
13907 -- Search the Rep_Item chain of entity E for an instance of a rep item
13908 -- (pragma, attribute definition clause, or aspect specification) whose
13909 -- name matches the given name Nam, and that has been inherited from its
13910 -- parent, i.e. that has not been directly specified for E . If one is
13911 -- found, it is returned, otherwise Empty is returned.
13913 function Get_Inherited_Rep_Item
13916 Nam2
: Name_Id
) return Node_Id
;
13917 -- Search the Rep_Item chain of entity E for an instance of a rep item
13918 -- (pragma, attribute definition clause, or aspect specification) whose
13919 -- name matches one of the given names Nam1 or Nam2, and that has been
13920 -- inherited from its parent, i.e. that has not been directly specified
13921 -- for E . If one is found, it is returned, otherwise Empty is returned.
13923 function Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
13924 (Rep_Item
: Node_Id
) return Boolean;
13925 -- This routine checks if Rep_Item is either a pragma or an aspect
13926 -- specification node whose corresponding pragma (if any) is present in
13927 -- the Rep Item chain of the entity it has been specified to.
13929 ----------------------------
13930 -- Get_Inherited_Rep_Item --
13931 ----------------------------
13933 function Get_Inherited_Rep_Item
13935 Nam
: Name_Id
) return Node_Id
13937 Rep
: constant Node_Id
13938 := Get_Rep_Item
(E
, Nam
, Check_Parents
=> True);
13941 and then not Has_Rep_Item
(E
, Nam
, Check_Parents
=> False)
13947 end Get_Inherited_Rep_Item
;
13949 function Get_Inherited_Rep_Item
13952 Nam2
: Name_Id
) return Node_Id
13954 Rep
: constant Node_Id
13955 := Get_Rep_Item
(E
, Nam1
, Nam2
, Check_Parents
=> True);
13958 and then not Has_Rep_Item
(E
, Nam1
, Nam2
, Check_Parents
=> False)
13964 end Get_Inherited_Rep_Item
;
13966 --------------------------------------------------
13967 -- Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item --
13968 --------------------------------------------------
13970 function Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
13971 (Rep_Item
: Node_Id
) return Boolean
13975 Nkind
(Rep_Item
) = N_Pragma
13977 Present_In_Rep_Item
(Entity
(Rep_Item
), Aspect_Rep_Item
(Rep_Item
));
13978 end Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
;
13982 -- Start of processing for Inherit_Aspects_At_Freeze_Point
13985 -- A representation item is either subtype-specific (Size and Alignment
13986 -- clauses) or type-related (all others). Subtype-specific aspects may
13987 -- differ for different subtypes of the same type (RM 13.1.8).
13989 -- A derived type inherits each type-related representation aspect of
13990 -- its parent type that was directly specified before the declaration of
13991 -- the derived type (RM 13.1.15).
13993 -- A derived subtype inherits each subtype-specific representation
13994 -- aspect of its parent subtype that was directly specified before the
13995 -- declaration of the derived type (RM 13.1.15).
13997 -- The general processing involves inheriting a representation aspect
13998 -- from a parent type whenever the first rep item (aspect specification,
13999 -- attribute definition clause, pragma) corresponding to the given
14000 -- representation aspect in the rep item chain of Typ, if any, isn't
14001 -- directly specified to Typ but to one of its parents.
14003 -- In addition, Convention must be propagated from base type to subtype,
14004 -- because the subtype may have been declared on an incomplete view.
14006 if Nkind
(Parent
(Typ
)) = N_Private_Extension_Declaration
then
14012 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Ada_05
, Name_Ada_2005
);
14014 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
14016 Set_Is_Ada_2005_Only
(Typ
);
14021 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Ada_12
, Name_Ada_2012
);
14023 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
14025 Set_Is_Ada_2012_Only
(Typ
);
14030 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Ada_2022
);
14032 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
14034 Set_Is_Ada_2022_Only
(Typ
);
14039 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Atomic
, Name_Shared
);
14041 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
14043 Set_Is_Atomic
(Typ
);
14044 Set_Is_Volatile
(Typ
);
14045 Set_Treat_As_Volatile
(Typ
);
14050 if Is_Record_Type
(Typ
)
14051 and then Typ
/= Base_Type
(Typ
) and then Is_Frozen
(Base_Type
(Typ
))
14053 Set_Convention
(Typ
, Convention
(Base_Type
(Typ
)));
14056 -- Default_Component_Value (for base types only)
14058 -- Note that we need to look into the first subtype because the base
14059 -- type may be the implicit base type built by the compiler for the
14060 -- declaration of a constrained subtype with the aspect.
14062 if Is_Array_Type
(Typ
) and then Is_Base_Type
(Typ
) then
14064 F_Typ
: constant Entity_Id
:= First_Subtype
(Typ
);
14070 Get_Inherited_Rep_Item
(F_Typ
, Name_Default_Component_Value
);
14071 if Present
(Rep
) then
14074 -- Deal with private types
14076 if Is_Private_Type
(E
) then
14077 E
:= Full_View
(E
);
14080 Set_Default_Aspect_Component_Value
14081 (Typ
, Default_Aspect_Component_Value
(E
));
14082 Set_Has_Default_Aspect
(Typ
);
14087 -- Default_Value (for base types only)
14089 -- Note that we need to look into the first subtype because the base
14090 -- type may be the implicit base type built by the compiler for the
14091 -- declaration of a constrained subtype with the aspect.
14093 if Is_Scalar_Type
(Typ
) and then Is_Base_Type
(Typ
) then
14095 F_Typ
: constant Entity_Id
:= First_Subtype
(Typ
);
14100 Rep
:= Get_Inherited_Rep_Item
(F_Typ
, Name_Default_Value
);
14101 if Present
(Rep
) then
14104 -- Deal with private types
14106 if Is_Private_Type
(E
) then
14107 E
:= Full_View
(E
);
14110 Set_Default_Aspect_Value
(Typ
, Default_Aspect_Value
(E
));
14111 Set_Has_Default_Aspect
(Typ
);
14118 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Discard_Names
);
14120 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
14122 Set_Discard_Names
(Typ
);
14127 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Volatile
);
14129 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
14131 Set_Is_Volatile
(Typ
);
14132 Set_Treat_As_Volatile
(Typ
);
14135 -- Volatile_Full_Access and Full_Access_Only
14137 Rep
:= Get_Inherited_Rep_Item
14138 (Typ
, Name_Volatile_Full_Access
, Name_Full_Access_Only
);
14140 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
14142 Set_Is_Volatile_Full_Access
(Typ
);
14143 Set_Is_Volatile
(Typ
);
14144 Set_Treat_As_Volatile
(Typ
);
14147 -- Inheritance for derived types only
14149 if Is_Derived_Type
(Typ
) then
14151 Bas_Typ
: constant Entity_Id
:= Base_Type
(Typ
);
14152 Imp_Bas_Typ
: constant Entity_Id
:= Implementation_Base_Type
(Typ
);
14155 -- Atomic_Components
14157 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Atomic_Components
);
14159 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
14161 Set_Has_Atomic_Components
(Imp_Bas_Typ
);
14164 -- Volatile_Components
14166 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Volatile_Components
);
14168 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
14170 Set_Has_Volatile_Components
(Imp_Bas_Typ
);
14173 -- Finalize_Storage_Only
14175 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Finalize_Storage_Only
);
14176 if Present
(Rep
) then
14177 Set_Finalize_Storage_Only
(Bas_Typ
);
14180 -- Universal_Aliasing
14182 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Universal_Aliasing
);
14184 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
(Rep
)
14186 Set_Universal_Aliasing
(Imp_Bas_Typ
);
14191 if Is_Record_Type
(Typ
) and then Typ
= Bas_Typ
then
14192 Rep
:= Get_Inherited_Rep_Item
(Typ
, Name_Bit_Order
);
14193 if Present
(Rep
) then
14194 Set_Reverse_Bit_Order
(Bas_Typ
,
14196 (Implementation_Base_Type
(Etype
(Bas_Typ
))));
14200 -- Scalar_Storage_Order
14202 if (Is_Record_Type
(Typ
) or else Is_Array_Type
(Typ
))
14203 and then Typ
= Bas_Typ
14205 -- For a type extension, always inherit from parent; otherwise
14206 -- inherit if no default applies. Note: we do not check for
14207 -- an explicit rep item on the parent type when inheriting,
14208 -- because the parent SSO may itself have been set by default.
14210 if not Has_Rep_Item
(First_Subtype
(Typ
),
14211 Name_Scalar_Storage_Order
, False)
14212 and then (Is_Tagged_Type
(Bas_Typ
)
14213 or else not (SSO_Set_Low_By_Default
(Bas_Typ
)
14215 SSO_Set_High_By_Default
(Bas_Typ
)))
14217 Set_Reverse_Storage_Order
(Bas_Typ
,
14218 Reverse_Storage_Order
14219 (Implementation_Base_Type
(Etype
(Bas_Typ
))));
14221 -- Clear default SSO indications, since the inherited aspect
14222 -- which was set explicitly overrides the default.
14224 Set_SSO_Set_Low_By_Default
(Bas_Typ
, False);
14225 Set_SSO_Set_High_By_Default
(Bas_Typ
, False);
14230 end Inherit_Aspects_At_Freeze_Point
;
14232 ---------------------------------
14233 -- Inherit_Delayed_Rep_Aspects --
14234 ---------------------------------
14236 procedure Inherit_Delayed_Rep_Aspects
(Typ
: Entity_Id
) is
14242 -- Find the first aspect that has been inherited
14244 N
:= First_Rep_Item
(Typ
);
14245 while Present
(N
) loop
14246 if Nkind
(N
) = N_Aspect_Specification
then
14247 exit when Entity
(N
) /= Typ
;
14253 -- There must be one if we reach here
14255 pragma Assert
(Present
(N
));
14258 -- Loop through delayed aspects for the parent type
14260 while Present
(N
) loop
14261 if Nkind
(N
) = N_Aspect_Specification
then
14262 exit when Entity
(N
) /= P
;
14264 if Is_Delayed_Aspect
(N
) then
14265 A
:= Get_Aspect_Id
(N
);
14267 -- Process delayed rep aspect. For Boolean attributes it is
14268 -- not possible to cancel an attribute once set (the attempt
14269 -- to use an aspect with xxx => False is an error) for a
14270 -- derived type. So for those cases, we do not have to check
14271 -- if a clause has been given for the derived type, since it
14272 -- is harmless to set it again if it is already set.
14278 when Aspect_Alignment
=>
14279 if not Has_Alignment_Clause
(Typ
) then
14280 Set_Alignment
(Typ
, Alignment
(P
));
14285 when Aspect_Atomic
=>
14286 if Is_Atomic
(P
) then
14287 Set_Is_Atomic
(Typ
);
14290 -- Atomic_Components
14292 when Aspect_Atomic_Components
=>
14293 if Has_Atomic_Components
(P
) then
14294 Set_Has_Atomic_Components
(Base_Type
(Typ
));
14299 when Aspect_Bit_Order
=>
14300 if Is_Record_Type
(Typ
)
14301 and then No
(Get_Attribute_Definition_Clause
14302 (Typ
, Attribute_Bit_Order
))
14303 and then Reverse_Bit_Order
(P
)
14305 Set_Reverse_Bit_Order
(Base_Type
(Typ
));
14310 when Aspect_Component_Size
=>
14311 if Is_Array_Type
(Typ
)
14312 and then not Has_Component_Size_Clause
(Typ
)
14315 (Base_Type
(Typ
), Component_Size
(P
));
14320 when Aspect_Machine_Radix
=>
14321 if Is_Decimal_Fixed_Point_Type
(Typ
)
14322 and then not Has_Machine_Radix_Clause
(Typ
)
14324 Set_Machine_Radix_10
(Typ
, Machine_Radix_10
(P
));
14327 -- Object_Size (also Size which also sets Object_Size)
14329 when Aspect_Object_Size
14332 if not Has_Size_Clause
(Typ
)
14334 No
(Get_Attribute_Definition_Clause
14335 (Typ
, Attribute_Object_Size
))
14337 Set_Esize
(Typ
, Esize
(P
));
14342 when Aspect_Pack
=>
14343 if not Is_Packed
(Typ
) then
14344 Set_Is_Packed
(Base_Type
(Typ
));
14346 if Is_Bit_Packed_Array
(P
) then
14347 Set_Is_Bit_Packed_Array
(Base_Type
(Typ
));
14348 Set_Packed_Array_Impl_Type
14349 (Typ
, Packed_Array_Impl_Type
(P
));
14353 -- Scalar_Storage_Order
14355 when Aspect_Scalar_Storage_Order
=>
14356 if (Is_Record_Type
(Typ
) or else Is_Array_Type
(Typ
))
14357 and then No
(Get_Attribute_Definition_Clause
14358 (Typ
, Attribute_Scalar_Storage_Order
))
14359 and then Reverse_Storage_Order
(P
)
14361 Set_Reverse_Storage_Order
(Base_Type
(Typ
));
14363 -- Clear default SSO indications, since the aspect
14364 -- overrides the default.
14366 Set_SSO_Set_Low_By_Default
(Base_Type
(Typ
), False);
14367 Set_SSO_Set_High_By_Default
(Base_Type
(Typ
), False);
14372 when Aspect_Small
=>
14373 if Is_Fixed_Point_Type
(Typ
)
14374 and then not Has_Small_Clause
(Typ
)
14376 Set_Small_Value
(Typ
, Small_Value
(P
));
14381 when Aspect_Storage_Size
=>
14382 if (Is_Access_Type
(Typ
) or else Is_Task_Type
(Typ
))
14383 and then not Has_Storage_Size_Clause
(Typ
)
14385 Set_Storage_Size_Variable
14386 (Base_Type
(Typ
), Storage_Size_Variable
(P
));
14391 when Aspect_Value_Size
=>
14393 -- Value_Size is never inherited, it is either set by
14394 -- default, or it is explicitly set for the derived
14395 -- type. So nothing to do here.
14401 when Aspect_Volatile
=>
14402 if Is_Volatile
(P
) then
14403 Set_Is_Volatile
(Typ
);
14406 -- Volatile_Full_Access (also Full_Access_Only)
14408 when Aspect_Volatile_Full_Access
14409 | Aspect_Full_Access_Only
14411 if Is_Volatile_Full_Access
(P
) then
14412 Set_Is_Volatile_Full_Access
(Typ
);
14415 -- Volatile_Components
14417 when Aspect_Volatile_Components
=>
14418 if Has_Volatile_Components
(P
) then
14419 Set_Has_Volatile_Components
(Base_Type
(Typ
));
14422 -- That should be all the Rep Aspects
14425 pragma Assert
(Aspect_Delay
(A
) /= Rep_Aspect
);
14433 end Inherit_Delayed_Rep_Aspects
;
14439 procedure Initialize
is
14441 Address_Clause_Checks
.Init
;
14442 Unchecked_Conversions
.Init
;
14444 -- The following might be needed in the future for some non-GCC back
14446 -- if AAMP_On_Target then
14447 -- Independence_Checks.Init;
14451 ---------------------------
14452 -- Install_Discriminants --
14453 ---------------------------
14455 procedure Install_Discriminants
(E
: Entity_Id
) is
14459 Disc
:= First_Discriminant
(E
);
14460 while Present
(Disc
) loop
14461 Prev
:= Current_Entity
(Disc
);
14462 Set_Current_Entity
(Disc
);
14463 Set_Is_Immediately_Visible
(Disc
);
14464 Set_Homonym
(Disc
, Prev
);
14465 Next_Discriminant
(Disc
);
14467 end Install_Discriminants
;
14469 -------------------------
14470 -- Is_Operational_Item --
14471 -------------------------
14473 function Is_Operational_Item
(N
: Node_Id
) return Boolean is
14475 -- List of operational items is given in AARM 13.1(8.mm/1). It is
14476 -- clearly incomplete, as it does not include iterator aspects, among
14479 return Nkind
(N
) = N_Attribute_Definition_Clause
14481 Get_Attribute_Id
(Chars
(N
)) in Attribute_Constant_Indexing
14482 | Attribute_External_Tag
14483 | Attribute_Default_Iterator
14484 | Attribute_Implicit_Dereference
14486 | Attribute_Iterable
14487 | Attribute_Iterator_Element
14489 | Attribute_Put_Image
14491 | Attribute_Variable_Indexing
14493 end Is_Operational_Item
;
14495 -------------------------
14496 -- Is_Predicate_Static --
14497 -------------------------
14499 -- Note: the basic legality of the expression has already been checked, so
14500 -- we don't need to worry about cases or ranges on strings for example.
14502 function Is_Predicate_Static
14505 Warn
: Boolean := True) return Boolean
14507 function All_Static_Case_Alternatives
(L
: List_Id
) return Boolean;
14508 -- Given a list of case expression alternatives, returns True if all
14509 -- the alternatives are static (have all static choices, and a static
14512 function Is_Type_Ref
(N
: Node_Id
) return Boolean;
14513 pragma Inline
(Is_Type_Ref
);
14514 -- Returns True if N is a reference to the type for the predicate in the
14515 -- expression (i.e. if it is an identifier whose Chars field matches the
14516 -- Nam given in the call). N must not be parenthesized, if the type name
14517 -- appears in parens, this routine will return False.
14519 -- The routine also returns True for function calls generated during the
14520 -- expansion of comparison operators on strings, which are intended to
14521 -- be legal in static predicates, and are converted into calls to array
14522 -- comparison routines in the body of the corresponding predicate
14525 ----------------------------------
14526 -- All_Static_Case_Alternatives --
14527 ----------------------------------
14529 function All_Static_Case_Alternatives
(L
: List_Id
) return Boolean is
14534 while Present
(N
) loop
14535 if not (All_Static_Choices
(Discrete_Choices
(N
))
14536 and then Is_OK_Static_Expression
(Expression
(N
)))
14545 end All_Static_Case_Alternatives
;
14551 function Is_Type_Ref
(N
: Node_Id
) return Boolean is
14553 return (Nkind
(N
) = N_Identifier
14554 and then Chars
(N
) = Nam
14555 and then Paren_Count
(N
) = 0);
14558 -- helper function for recursive calls
14559 function Is_Predicate_Static_Aux
(Expr
: Node_Id
) return Boolean is
14560 (Is_Predicate_Static
(Expr
, Nam
, Warn
=> False));
14562 -- Start of processing for Is_Predicate_Static
14565 -- Handle cases like
14566 -- subtype S is Integer with Static_Predicate =>
14567 -- (Some_Integer_Variable in Integer) and then (S /= 0);
14568 -- where the predicate (which should be rejected) might have been
14569 -- transformed into just "(S /= 0)", which would appear to be
14570 -- a predicate-static expression (and therefore legal).
14572 if Is_Rewrite_Substitution
(Expr
) then
14574 -- Emit warnings for predicates that are always True or always False
14575 -- and were not originally expressed as Boolean literals.
14577 return Result
: constant Boolean :=
14578 Is_Predicate_Static_Aux
(Original_Node
(Expr
))
14580 if Result
and then Warn
and then Is_Entity_Name
(Expr
) then
14581 if Entity
(Expr
) = Standard_True
then
14582 Error_Msg_N
("predicate is redundant (always True)?", Expr
);
14583 elsif Entity
(Expr
) = Standard_False
then
14585 ("predicate is unsatisfiable (always False)?", Expr
);
14591 -- Predicate_Static means one of the following holds. Numbers are the
14592 -- corresponding paragraph numbers in (RM 3.2.4(16-22)).
14594 -- 16: A static expression
14596 if Is_OK_Static_Expression
(Expr
) then
14599 -- 17: A membership test whose simple_expression is the current
14600 -- instance, and whose membership_choice_list meets the requirements
14601 -- for a static membership test.
14603 elsif Nkind
(Expr
) in N_Membership_Test
14604 and then Is_Type_Ref
(Left_Opnd
(Expr
))
14605 and then All_Membership_Choices_Static
(Expr
)
14609 -- 18. A case_expression whose selecting_expression is the current
14610 -- instance, and whose dependent expressions are static expressions.
14612 elsif Nkind
(Expr
) = N_Case_Expression
14613 and then Is_Type_Ref
(Expression
(Expr
))
14614 and then All_Static_Case_Alternatives
(Alternatives
(Expr
))
14618 -- 19. A call to a predefined equality or ordering operator, where one
14619 -- operand is the current instance, and the other is a static
14622 -- Note: the RM is clearly wrong here in not excluding string types.
14623 -- Without this exclusion, we would allow expressions like X > "ABC"
14624 -- to be considered as predicate-static, which is clearly not intended,
14625 -- since the idea is for predicate-static to be a subset of normal
14626 -- static expressions (and "DEF" > "ABC" is not a static expression).
14628 -- However, we do allow internally generated (not from source) equality
14629 -- and inequality operations to be valid on strings (this helps deal
14630 -- with cases where we transform A in "ABC" to A = "ABC).
14632 -- In fact, it appears that the intent of the ARG is to extend static
14633 -- predicates to strings, and that the extension should probably apply
14634 -- to static expressions themselves. The code below accepts comparison
14635 -- operators that apply to static strings.
14637 elsif Nkind
(Expr
) in N_Op_Compare
14638 and then ((Is_Type_Ref
(Left_Opnd
(Expr
))
14639 and then Is_OK_Static_Expression
(Right_Opnd
(Expr
)))
14641 (Is_Type_Ref
(Right_Opnd
(Expr
))
14642 and then Is_OK_Static_Expression
(Left_Opnd
(Expr
))))
14646 -- 20. A call to a predefined boolean logical operator, where each
14647 -- operand is predicate-static.
14649 elsif (Nkind
(Expr
) in N_Op_And | N_Op_Or | N_Op_Xor
14650 and then Is_Predicate_Static_Aux
(Left_Opnd
(Expr
))
14651 and then Is_Predicate_Static_Aux
(Right_Opnd
(Expr
)))
14653 (Nkind
(Expr
) = N_Op_Not
14654 and then Is_Predicate_Static_Aux
(Right_Opnd
(Expr
)))
14658 -- 21. A short-circuit control form where both operands are
14659 -- predicate-static.
14661 elsif Nkind
(Expr
) in N_Short_Circuit
14662 and then Is_Predicate_Static_Aux
(Left_Opnd
(Expr
))
14663 and then Is_Predicate_Static_Aux
(Right_Opnd
(Expr
))
14667 -- 22. A parenthesized predicate-static expression. This does not
14668 -- require any special test, since we just ignore paren levels in
14669 -- all the cases above.
14671 -- One more test that is an implementation artifact caused by the fact
14672 -- that we are analyzing not the original expression, but the generated
14673 -- expression in the body of the predicate function. This can include
14674 -- references to inherited predicates, so that the expression we are
14675 -- processing looks like:
14677 -- xxPredicate (typ (Inns)) and then expression
14679 -- Where the call is to a Predicate function for an inherited predicate.
14680 -- We simply ignore such a call, which could be to either a dynamic or
14681 -- a static predicate. Note that if the parent predicate is dynamic then
14682 -- eventually this type will be marked as dynamic, but you are allowed
14683 -- to specify a static predicate for a subtype which is inheriting a
14684 -- dynamic predicate, so the static predicate validation here ignores
14685 -- the inherited predicate even if it is dynamic.
14686 -- In all cases, a static predicate can only apply to a scalar type.
14688 elsif Nkind
(Expr
) = N_Function_Call
14689 and then Is_Predicate_Function
(Entity
(Name
(Expr
)))
14690 and then Is_Scalar_Type
(Etype
(First_Entity
(Entity
(Name
(Expr
)))))
14694 -- That's an exhaustive list of tests, all other cases are not
14695 -- predicate-static, so we return False.
14700 end Is_Predicate_Static
;
14702 ----------------------
14703 -- Is_Static_Choice --
14704 ----------------------
14706 function Is_Static_Choice
(N
: Node_Id
) return Boolean is
14708 return Nkind
(N
) = N_Others_Choice
14709 or else Is_OK_Static_Expression
(N
)
14710 or else (Is_Entity_Name
(N
) and then Is_Type
(Entity
(N
))
14711 and then Is_OK_Static_Subtype
(Entity
(N
)))
14712 or else (Nkind
(N
) = N_Subtype_Indication
14713 and then Is_OK_Static_Subtype
(Entity
(N
)))
14714 or else (Nkind
(N
) = N_Range
and then Is_OK_Static_Range
(N
));
14715 end Is_Static_Choice
;
14717 ------------------------------
14718 -- Is_Type_Related_Rep_Item --
14719 ------------------------------
14721 function Is_Type_Related_Rep_Item
(N
: Node_Id
) return Boolean is
14724 when N_Attribute_Definition_Clause
=>
14725 -- See AARM 13.1(8.f-8.x) list items that end in "clause"
14726 -- ???: include any GNAT-defined attributes here?
14727 return Get_Attribute_Id
(Chars
(N
)) in Attribute_Bit_Order
14728 | Attribute_Component_Size
14729 | Attribute_Machine_Radix
14730 | Attribute_Storage_Pool
14731 | Attribute_Stream_Size
;
14734 case Get_Pragma_Id
(N
) is
14735 -- See AARM 13.1(8.f-8.x) list items that start with "pragma"
14736 -- ???: include any GNAT-defined pragmas here?
14740 | Pragma_Convention
14742 | Pragma_Independent
14744 | Pragma_Atomic_Components
14745 | Pragma_Independent_Components
14746 | Pragma_Volatile_Components
14747 | Pragma_Discard_Names
14754 when N_Enumeration_Representation_Clause
14755 | N_Record_Representation_Clause
14764 end Is_Type_Related_Rep_Item
;
14766 ---------------------
14767 -- Kill_Rep_Clause --
14768 ---------------------
14770 procedure Kill_Rep_Clause
(N
: Node_Id
) is
14772 pragma Assert
(Ignore_Rep_Clauses
);
14774 -- Note: we use Replace rather than Rewrite, because we don't want
14775 -- tools to be able to use Original_Node to dig out the (undecorated)
14776 -- rep clause that is being replaced.
14778 Replace
(N
, Make_Null_Statement
(Sloc
(N
)));
14780 -- The null statement must be marked as not coming from source. This is
14781 -- so that tools ignore it, and also the back end does not expect bogus
14782 -- "from source" null statements in weird places (e.g. in declarative
14783 -- regions where such null statements are not allowed).
14785 Set_Comes_From_Source
(N
, False);
14786 end Kill_Rep_Clause
;
14792 function Minimum_Size
14794 Biased
: Boolean := False) return Int
14796 Lo
: Uint
:= No_Uint
;
14797 Hi
: Uint
:= No_Uint
;
14798 LoR
: Ureal
:= No_Ureal
;
14799 HiR
: Ureal
:= No_Ureal
;
14800 LoSet
: Boolean := False;
14801 HiSet
: Boolean := False;
14804 Ancest
: Entity_Id
;
14805 R_Typ
: constant Entity_Id
:= Root_Type
(T
);
14810 if T
= Any_Type
then
14811 return Unknown_Minimum_Size
;
14813 -- For generic types, just return unknown. There cannot be any
14814 -- legitimate need to know such a size, but this routine may be
14815 -- called with a generic type as part of normal processing.
14817 elsif Is_Generic_Type
(R_Typ
) or else R_Typ
= Any_Type
then
14818 return Unknown_Minimum_Size
;
14820 -- Access types (cannot have size smaller than System.Address)
14822 elsif Is_Access_Type
(T
) then
14823 return System_Address_Size
;
14825 -- Floating-point types
14827 elsif Is_Floating_Point_Type
(T
) then
14828 return UI_To_Int
(Esize
(R_Typ
));
14832 elsif Is_Discrete_Type
(T
) then
14834 -- The following loop is looking for the nearest compile time known
14835 -- bounds following the ancestor subtype chain. The idea is to find
14836 -- the most restrictive known bounds information.
14840 if Ancest
= Any_Type
or else Etype
(Ancest
) = Any_Type
then
14841 return Unknown_Minimum_Size
;
14845 if Compile_Time_Known_Value
(Type_Low_Bound
(Ancest
)) then
14846 Lo
:= Expr_Rep_Value
(Type_Low_Bound
(Ancest
));
14853 if Compile_Time_Known_Value
(Type_High_Bound
(Ancest
)) then
14854 Hi
:= Expr_Rep_Value
(Type_High_Bound
(Ancest
));
14860 Ancest
:= Ancestor_Subtype
(Ancest
);
14862 if No
(Ancest
) then
14863 Ancest
:= Base_Type
(T
);
14865 if Is_Generic_Type
(Ancest
) then
14866 return Unknown_Minimum_Size
;
14871 -- Fixed-point types. We can't simply use Expr_Value to get the
14872 -- Corresponding_Integer_Value values of the bounds, since these do not
14873 -- get set till the type is frozen, and this routine can be called
14874 -- before the type is frozen. Similarly the test for bounds being static
14875 -- needs to include the case where we have unanalyzed real literals for
14876 -- the same reason.
14878 elsif Is_Fixed_Point_Type
(T
) then
14880 -- The following loop is looking for the nearest compile time known
14881 -- bounds following the ancestor subtype chain. The idea is to find
14882 -- the most restrictive known bounds information.
14886 if Ancest
= Any_Type
or else Etype
(Ancest
) = Any_Type
then
14887 return Unknown_Minimum_Size
;
14890 -- Note: In the following two tests for LoSet and HiSet, it may
14891 -- seem redundant to test for N_Real_Literal here since normally
14892 -- one would assume that the test for the value being known at
14893 -- compile time includes this case. However, there is a glitch.
14894 -- If the real literal comes from folding a non-static expression,
14895 -- then we don't consider any non- static expression to be known
14896 -- at compile time if we are in configurable run time mode (needed
14897 -- in some cases to give a clearer definition of what is and what
14898 -- is not accepted). So the test is indeed needed. Without it, we
14899 -- would set neither Lo_Set nor Hi_Set and get an infinite loop.
14902 if Nkind
(Type_Low_Bound
(Ancest
)) = N_Real_Literal
14903 or else Compile_Time_Known_Value
(Type_Low_Bound
(Ancest
))
14905 LoR
:= Expr_Value_R
(Type_Low_Bound
(Ancest
));
14912 if Nkind
(Type_High_Bound
(Ancest
)) = N_Real_Literal
14913 or else Compile_Time_Known_Value
(Type_High_Bound
(Ancest
))
14915 HiR
:= Expr_Value_R
(Type_High_Bound
(Ancest
));
14921 Ancest
:= Ancestor_Subtype
(Ancest
);
14923 if No
(Ancest
) then
14924 Ancest
:= Base_Type
(T
);
14926 if Is_Generic_Type
(Ancest
) then
14927 return Unknown_Minimum_Size
;
14932 Lo
:= UR_To_Uint
(LoR
/ Small_Value
(T
));
14933 Hi
:= UR_To_Uint
(HiR
/ Small_Value
(T
));
14935 -- No other types allowed
14938 raise Program_Error
;
14941 -- Fall through with Hi and Lo set. Deal with biased case
14944 and then not Is_Fixed_Point_Type
(T
)
14945 and then not (Is_Enumeration_Type
(T
)
14946 and then Has_Non_Standard_Rep
(T
)))
14947 or else Has_Biased_Representation
(T
)
14953 -- Null range case, size is always zero. We only do this in the discrete
14954 -- type case, since that's the odd case that came up. Probably we should
14955 -- also do this in the fixed-point case, but doing so causes peculiar
14956 -- gigi failures, and it is not worth worrying about this incredibly
14957 -- marginal case (explicit null-range fixed-point type declarations).
14959 if Lo
> Hi
and then Is_Discrete_Type
(T
) then
14962 -- Signed case. Note that we consider types like range 1 .. -1 to be
14963 -- signed for the purpose of computing the size, since the bounds have
14964 -- to be accommodated in the base type.
14966 elsif Lo
< 0 or else Hi
< 0 then
14970 -- S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
14971 -- Note that we accommodate the case where the bounds cross. This
14972 -- can happen either because of the way the bounds are declared
14973 -- or because of the algorithm in Freeze_Fixed_Point_Type.
14987 -- If both bounds are positive, make sure that both are represen-
14988 -- table in the case where the bounds are crossed. This can happen
14989 -- either because of the way the bounds are declared, or because of
14990 -- the algorithm in Freeze_Fixed_Point_Type.
14996 -- S = size, (can accommodate 0 .. (2**size - 1))
14999 while Hi
>= Uint_2
** S
loop
15007 ------------------------------
15008 -- New_Put_Image_Subprogram --
15009 ------------------------------
15011 procedure New_Put_Image_Subprogram
15016 Loc
: constant Source_Ptr
:= Sloc
(N
);
15017 Sname
: constant Name_Id
:=
15018 Make_TSS_Name
(Base_Type
(Ent
), TSS_Put_Image
);
15019 Subp_Id
: Entity_Id
;
15020 Subp_Decl
: Node_Id
;
15024 Defer_Declaration
: constant Boolean :=
15025 Is_Tagged_Type
(Ent
) or else Is_Private_Type
(Ent
);
15026 -- For a tagged type, there is a declaration at the freeze point, and
15027 -- we must generate only a completion of this declaration. We do the
15028 -- same for private types, because the full view might be tagged.
15029 -- Otherwise we generate a declaration at the point of the attribute
15030 -- definition clause. If the attribute definition comes from an aspect
15031 -- specification the declaration is part of the freeze actions of the
15034 function Build_Spec
return Node_Id
;
15035 -- Used for declaration and renaming declaration, so that this is
15036 -- treated as a renaming_as_body.
15042 function Build_Spec
return Node_Id
is
15045 T_Ref
: constant Node_Id
:= New_Occurrence_Of
(Etyp
, Loc
);
15048 Subp_Id
:= Make_Defining_Identifier
(Loc
, Sname
);
15050 -- S : Root_Buffer_Type'Class
15052 Formals
:= New_List
(
15053 Make_Parameter_Specification
(Loc
,
15054 Defining_Identifier
=>
15055 Make_Defining_Identifier
(Loc
, Name_S
),
15056 In_Present
=> True,
15057 Out_Present
=> True,
15059 New_Occurrence_Of
(Etype
(F
), Loc
)));
15063 Append_To
(Formals
,
15064 Make_Parameter_Specification
(Loc
,
15065 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_V
),
15066 Parameter_Type
=> T_Ref
));
15069 Make_Procedure_Specification
(Loc
,
15070 Defining_Unit_Name
=> Subp_Id
,
15071 Parameter_Specifications
=> Formals
);
15076 -- Start of processing for New_Put_Image_Subprogram
15079 F
:= First_Formal
(Subp
);
15081 Etyp
:= Etype
(Next_Formal
(F
));
15083 -- Prepare subprogram declaration and insert it as an action on the
15084 -- clause node. The visibility for this entity is used to test for
15085 -- visibility of the attribute definition clause (in the sense of
15086 -- 8.3(23) as amended by AI-195).
15088 if not Defer_Declaration
then
15090 Make_Subprogram_Declaration
(Loc
,
15091 Specification
=> Build_Spec
);
15093 -- For a tagged type, there is always a visible declaration for the
15094 -- Put_Image TSS (it is a predefined primitive operation), and the
15095 -- completion of this declaration occurs at the freeze point, which is
15096 -- not always visible at places where the attribute definition clause is
15097 -- visible. So, we create a dummy entity here for the purpose of
15098 -- tracking the visibility of the attribute definition clause itself.
15102 Make_Defining_Identifier
(Loc
, New_External_Name
(Sname
, 'V'));
15104 Make_Object_Declaration
(Loc
,
15105 Defining_Identifier
=> Subp_Id
,
15106 Object_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
));
15109 if not Defer_Declaration
15110 and then From_Aspect_Specification
(N
)
15111 and then Has_Delayed_Freeze
(Ent
)
15113 Append_Freeze_Action
(Ent
, Subp_Decl
);
15116 Insert_Action
(N
, Subp_Decl
);
15117 Set_Entity
(N
, Subp_Id
);
15121 Make_Subprogram_Renaming_Declaration
(Loc
,
15122 Specification
=> Build_Spec
,
15123 Name
=> New_Occurrence_Of
(Subp
, Loc
));
15125 if Defer_Declaration
then
15126 Set_TSS
(Base_Type
(Ent
), Subp_Id
);
15129 if From_Aspect_Specification
(N
) then
15130 Append_Freeze_Action
(Ent
, Subp_Decl
);
15132 Insert_Action
(N
, Subp_Decl
);
15135 Copy_TSS
(Subp_Id
, Base_Type
(Ent
));
15137 end New_Put_Image_Subprogram
;
15139 ---------------------------
15140 -- New_Stream_Subprogram --
15141 ---------------------------
15143 procedure New_Stream_Subprogram
15147 Nam
: TSS_Name_Type
)
15149 Loc
: constant Source_Ptr
:= Sloc
(N
);
15150 Sname
: constant Name_Id
:= Make_TSS_Name
(Base_Type
(Ent
), Nam
);
15151 Subp_Id
: Entity_Id
;
15152 Subp_Decl
: Node_Id
;
15156 Defer_Declaration
: constant Boolean :=
15157 Is_Tagged_Type
(Ent
) or else Is_Private_Type
(Ent
);
15158 -- For a tagged type, there is a declaration for each stream attribute
15159 -- at the freeze point, and we must generate only a completion of this
15160 -- declaration. We do the same for private types, because the full view
15161 -- might be tagged. Otherwise we generate a declaration at the point of
15162 -- the attribute definition clause. If the attribute definition comes
15163 -- from an aspect specification the declaration is part of the freeze
15164 -- actions of the type.
15166 function Build_Spec
return Node_Id
;
15167 -- Used for declaration and renaming declaration, so that this is
15168 -- treated as a renaming_as_body.
15174 function Build_Spec
return Node_Id
is
15175 Out_P
: constant Boolean := (Nam
= TSS_Stream_Read
);
15178 T_Ref
: constant Node_Id
:= New_Occurrence_Of
(Etyp
, Loc
);
15181 Subp_Id
:= Make_Defining_Identifier
(Loc
, Sname
);
15183 -- S : access Root_Stream_Type'Class
15185 Formals
:= New_List
(
15186 Make_Parameter_Specification
(Loc
,
15187 Defining_Identifier
=>
15188 Make_Defining_Identifier
(Loc
, Name_S
),
15190 Make_Access_Definition
(Loc
,
15192 New_Occurrence_Of
(
15193 Designated_Type
(Etype
(F
)), Loc
))));
15195 if Nam
= TSS_Stream_Input
then
15197 Make_Function_Specification
(Loc
,
15198 Defining_Unit_Name
=> Subp_Id
,
15199 Parameter_Specifications
=> Formals
,
15200 Result_Definition
=> T_Ref
);
15204 Append_To
(Formals
,
15205 Make_Parameter_Specification
(Loc
,
15206 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_V
),
15207 Out_Present
=> Out_P
,
15208 Parameter_Type
=> T_Ref
));
15211 Make_Procedure_Specification
(Loc
,
15212 Defining_Unit_Name
=> Subp_Id
,
15213 Parameter_Specifications
=> Formals
);
15219 -- Start of processing for New_Stream_Subprogram
15222 F
:= First_Formal
(Subp
);
15224 if Ekind
(Subp
) = E_Procedure
then
15225 Etyp
:= Etype
(Next_Formal
(F
));
15227 Etyp
:= Etype
(Subp
);
15230 -- Prepare subprogram declaration and insert it as an action on the
15231 -- clause node. The visibility for this entity is used to test for
15232 -- visibility of the attribute definition clause (in the sense of
15233 -- 8.3(23) as amended by AI-195).
15235 if not Defer_Declaration
then
15237 Make_Subprogram_Declaration
(Loc
,
15238 Specification
=> Build_Spec
);
15240 -- For a tagged type, there is always a visible declaration for each
15241 -- stream TSS (it is a predefined primitive operation), and the
15242 -- completion of this declaration occurs at the freeze point, which is
15243 -- not always visible at places where the attribute definition clause is
15244 -- visible. So, we create a dummy entity here for the purpose of
15245 -- tracking the visibility of the attribute definition clause itself.
15249 Make_Defining_Identifier
(Loc
, New_External_Name
(Sname
, 'V'));
15251 Make_Object_Declaration
(Loc
,
15252 Defining_Identifier
=> Subp_Id
,
15253 Object_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
));
15256 if not Defer_Declaration
15257 and then From_Aspect_Specification
(N
)
15258 and then Has_Delayed_Freeze
(Ent
)
15260 Append_Freeze_Action
(Ent
, Subp_Decl
);
15263 Insert_Action
(N
, Subp_Decl
);
15264 Set_Entity
(N
, Subp_Id
);
15268 Make_Subprogram_Renaming_Declaration
(Loc
,
15269 Specification
=> Build_Spec
,
15270 Name
=> New_Occurrence_Of
(Subp
, Loc
));
15272 if Defer_Declaration
then
15273 Set_TSS
(Base_Type
(Ent
), Subp_Id
);
15276 if From_Aspect_Specification
(N
) then
15277 Append_Freeze_Action
(Ent
, Subp_Decl
);
15279 Insert_Action
(N
, Subp_Decl
);
15282 Copy_TSS
(Subp_Id
, Base_Type
(Ent
));
15284 end New_Stream_Subprogram
;
15286 ----------------------
15287 -- No_Type_Rep_Item --
15288 ----------------------
15290 procedure No_Type_Rep_Item
(N
: Node_Id
) is
15292 Error_Msg_N
("|type-related representation item not permitted!", N
);
15293 end No_Type_Rep_Item
;
15299 procedure Pop_Type
(E
: Entity_Id
) is
15301 if Ekind
(E
) = E_Record_Type
and then E
= Current_Scope
then
15305 and then Has_Discriminants
(E
)
15306 and then Nkind
(Parent
(E
)) /= N_Subtype_Declaration
15308 Uninstall_Discriminants
(E
);
15317 procedure Push_Type
(E
: Entity_Id
) is
15321 if Ekind
(E
) = E_Record_Type
then
15324 Comp
:= First_Component
(E
);
15325 while Present
(Comp
) loop
15326 Install_Entity
(Comp
);
15327 Next_Component
(Comp
);
15330 if Has_Discriminants
(E
) then
15331 Install_Discriminants
(E
);
15335 and then Has_Discriminants
(E
)
15336 and then Nkind
(Parent
(E
)) /= N_Subtype_Declaration
15339 Install_Discriminants
(E
);
15343 -----------------------------------
15344 -- Register_Address_Clause_Check --
15345 -----------------------------------
15347 procedure Register_Address_Clause_Check
15354 ACS
: constant Boolean := Scope_Suppress
.Suppress
(Alignment_Check
);
15356 Address_Clause_Checks
.Append
((N
, X
, A
, Y
, Off
, ACS
));
15357 end Register_Address_Clause_Check
;
15359 ------------------------
15360 -- Rep_Item_Too_Early --
15361 ------------------------
15363 function Rep_Item_Too_Early
(T
: Entity_Id
; N
: Node_Id
) return Boolean is
15364 function Has_Generic_Parent
(E
: Entity_Id
) return Boolean;
15365 -- Return True if R or any ancestor is a generic type
15367 ------------------------
15368 -- Has_Generic_Parent --
15369 ------------------------
15371 function Has_Generic_Parent
(E
: Entity_Id
) return Boolean is
15372 Ancestor_Type
: Entity_Id
:= Etype
(E
);
15375 if Is_Generic_Type
(E
) then
15379 while Present
(Ancestor_Type
)
15380 and then not Is_Generic_Type
(Ancestor_Type
)
15381 and then Etype
(Ancestor_Type
) /= Ancestor_Type
15383 Ancestor_Type
:= Etype
(Ancestor_Type
);
15387 Present
(Ancestor_Type
) and then Is_Generic_Type
(Ancestor_Type
);
15388 end Has_Generic_Parent
;
15390 -- Start of processing for Rep_Item_Too_Early
15393 -- Cannot apply non-operational rep items to generic types
15395 if Is_Operational_Item
(N
) then
15399 and then Has_Generic_Parent
(T
)
15400 and then (Nkind
(N
) /= N_Pragma
15401 or else Get_Pragma_Id
(N
) /= Pragma_Convention
)
15403 if Ada_Version
< Ada_2022
then
15405 ("representation item not allowed for generic type", N
);
15412 -- Otherwise check for incomplete type
15414 if Is_Incomplete_Or_Private_Type
(T
)
15415 and then No
(Underlying_Type
(T
))
15417 (Nkind
(N
) /= N_Pragma
15418 or else Get_Pragma_Id
(N
) /= Pragma_Import
)
15421 ("representation item must be after full type declaration", N
);
15424 -- If the type has incomplete components, a representation clause is
15425 -- illegal but stream attributes and Convention pragmas are correct.
15427 elsif Has_Private_Component
(T
) then
15428 if Nkind
(N
) = N_Pragma
then
15433 ("representation item must appear after type is fully defined",
15440 end Rep_Item_Too_Early
;
15442 -----------------------
15443 -- Rep_Item_Too_Late --
15444 -----------------------
15446 function Rep_Item_Too_Late
15449 FOnly
: Boolean := False) return Boolean
15451 procedure Too_Late
;
15452 -- Output message for an aspect being specified too late
15454 -- Note that neither of the above errors is considered a serious one,
15455 -- since the effect is simply that we ignore the representation clause
15457 -- Is this really true? In any case if we make this change we must
15458 -- document the requirement in the spec of Rep_Item_Too_Late that
15459 -- if True is returned, then the rep item must be completely ignored???
15465 procedure Too_Late
is
15467 -- Other compilers seem more relaxed about rep items appearing too
15468 -- late. Since analysis tools typically don't care about rep items
15469 -- anyway, no reason to be too strict about this.
15471 if not Relaxed_RM_Semantics
then
15472 Error_Msg_N
("|representation item appears too late!", N
);
15478 Parent_Type
: Entity_Id
;
15481 -- Start of processing for Rep_Item_Too_Late
15484 -- First make sure entity is not frozen (RM 13.1(9))
15488 -- Exclude imported types, which may be frozen if they appear in a
15489 -- representation clause for a local type.
15491 and then not From_Limited_With
(T
)
15493 -- Exclude generated entities (not coming from source). The common
15494 -- case is when we generate a renaming which prematurely freezes the
15495 -- renamed internal entity, but we still want to be able to set copies
15496 -- of attribute values such as Size/Alignment.
15498 and then Comes_From_Source
(T
)
15500 -- A self-referential aspect is illegal if it forces freezing the
15501 -- entity before the corresponding pragma has been analyzed.
15503 if Nkind
(N
) in N_Attribute_Definition_Clause | N_Pragma
15504 and then From_Aspect_Specification
(N
)
15507 ("aspect specification causes premature freezing of&", N
, T
);
15508 Set_Has_Delayed_Freeze
(T
, False);
15513 S
:= First_Subtype
(T
);
15515 if Present
(Freeze_Node
(S
)) then
15516 if not Relaxed_RM_Semantics
then
15518 ("??no more representation items for }", Freeze_Node
(S
), S
);
15524 -- Check for case of untagged derived type whose parent either has
15525 -- primitive operations (pre Ada 2022), or is a by-reference type (RM
15526 -- 13.1(10)). In this case we do not output a Too_Late message, since
15527 -- there is no earlier point where the rep item could be placed to make
15529 -- ??? Confirming representation clauses should be allowed here.
15533 and then Is_Derived_Type
(T
)
15534 and then not Is_Tagged_Type
(T
)
15536 Parent_Type
:= Etype
(Base_Type
(T
));
15538 if Relaxed_RM_Semantics
then
15541 elsif Ada_Version
<= Ada_2012
15542 and then Has_Primitive_Operations
(Parent_Type
)
15545 ("|representation item not permitted before Ada 2022!", N
);
15547 ("\parent type & has primitive operations!", N
, Parent_Type
);
15550 elsif Is_By_Reference_Type
(Parent_Type
) then
15551 No_Type_Rep_Item
(N
);
15553 ("\parent type & is a by-reference type!", N
, Parent_Type
);
15558 -- No error, but one more warning to consider. The RM (surprisingly)
15559 -- allows this pattern in some cases:
15562 -- primitive operations for S
15563 -- type R is new S;
15564 -- rep clause for S
15566 -- Meaning that calls on the primitive operations of S for values of
15567 -- type R may require possibly expensive implicit conversion operations.
15568 -- So even when this is not an error, it is still worth a warning.
15570 if not Relaxed_RM_Semantics
and then Is_Type
(T
) then
15572 DTL
: constant Entity_Id
:= Derived_Type_Link
(Base_Type
(T
));
15577 -- For now, do not generate this warning for the case of
15578 -- aspect specification using Ada 2012 syntax, since we get
15579 -- wrong messages we do not understand. The whole business
15580 -- of derived types and rep items seems a bit confused when
15581 -- aspects are used, since the aspects are not evaluated
15582 -- till freeze time. However, AI12-0109 confirms (in an AARM
15583 -- ramification) that inheritance in this case is required
15586 and then not From_Aspect_Specification
(N
)
15588 if Is_By_Reference_Type
(T
)
15589 and then not Is_Tagged_Type
(T
)
15590 and then Is_Type_Related_Rep_Item
(N
)
15591 and then (Ada_Version
>= Ada_2012
15592 or else Has_Primitive_Operations
(Base_Type
(T
)))
15594 -- Treat as hard error (AI12-0109, binding interpretation).
15595 -- Implementing a change of representation is not really
15596 -- an option in the case of a by-reference type, so we
15597 -- take this path for all Ada dialects if primitive
15598 -- operations are present.
15599 Error_Msg_Sloc
:= Sloc
(DTL
);
15601 ("representation item for& appears after derived type "
15602 & "declaration#", N
);
15604 elsif Has_Primitive_Operations
(Base_Type
(T
)) then
15605 Error_Msg_Sloc
:= Sloc
(DTL
);
15608 ("representation item for& appears after derived type "
15609 & "declaration#??", N
);
15611 ("\may result in implicit conversions for primitive "
15612 & "operations of&??", N
, T
);
15614 ("\to change representations when called with arguments "
15615 & "of type&??", N
, DTL
);
15621 -- No error, link item into head of chain of rep items for the entity,
15622 -- but avoid chaining if we have an overloadable entity, and the pragma
15623 -- is one that can apply to multiple overloaded entities.
15625 if Is_Overloadable
(T
) and then Nkind
(N
) = N_Pragma
then
15627 Pname
: constant Name_Id
:= Pragma_Name
(N
);
15629 if Pname
in Name_Convention | Name_Import | Name_Export
15630 | Name_External | Name_Interface
15637 Record_Rep_Item
(T
, N
);
15639 end Rep_Item_Too_Late
;
15641 -------------------------------------
15642 -- Replace_Type_References_Generic --
15643 -------------------------------------
15645 procedure Replace_Type_References_Generic
(N
: Node_Id
; T
: Entity_Id
) is
15646 TName
: constant Name_Id
:= Chars
(T
);
15648 function Replace_Type_Ref
(N
: Node_Id
) return Traverse_Result
;
15649 -- Processes a single node in the traversal procedure below, checking
15650 -- if node N should be replaced, and if so, doing the replacement.
15652 function Visible_Component
(Comp
: Name_Id
) return Entity_Id
;
15653 -- Given an identifier in the expression, check whether there is a
15654 -- discriminant, component, protected procedure, or entry of the type
15655 -- that is directy visible, and rewrite it as the corresponding selected
15656 -- component of the formal of the subprogram.
15658 ----------------------
15659 -- Replace_Type_Ref --
15660 ----------------------
15662 function Replace_Type_Ref
(N
: Node_Id
) return Traverse_Result
is
15663 Loc
: constant Source_Ptr
:= Sloc
(N
);
15665 procedure Add_Prefix
(Ref
: Node_Id
; Comp
: Entity_Id
);
15666 -- Add the proper prefix to a reference to a component of the type
15667 -- when it is not already a selected component.
15673 procedure Add_Prefix
(Ref
: Node_Id
; Comp
: Entity_Id
) is
15676 Make_Selected_Component
(Loc
,
15677 Prefix
=> New_Occurrence_Of
(T
, Loc
),
15678 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
)));
15679 Replace_Type_Reference
(Prefix
(Ref
));
15688 -- Start of processing for Replace_Type_Ref
15691 if Nkind
(N
) = N_Identifier
then
15693 -- If not the type name, check whether it is a reference to some
15694 -- other type, which must be frozen before the predicate function
15695 -- is analyzed, i.e. before the freeze node of the type to which
15696 -- the predicate applies.
15698 if Chars
(N
) /= TName
then
15699 if Present
(Current_Entity
(N
))
15700 and then Is_Type
(Current_Entity
(N
))
15702 Freeze_Before
(Freeze_Node
(T
), Current_Entity
(N
));
15705 -- The components of the type are directly visible and can
15706 -- be referenced in the source code without a prefix.
15707 -- If a name denoting a component doesn't already have a
15708 -- prefix, then normalize it by adding a reference to the
15709 -- current instance of the type as a prefix.
15711 -- This isn't right in the pathological corner case of an
15712 -- object-declaring expression (e.g., a quantified expression
15713 -- or a declare expression) that declares an object with the
15714 -- same name as a visible component declaration, thereby hiding
15715 -- the component within that expression. For example, given a
15716 -- record with a Boolean component "C" and a dynamic predicate
15717 -- "C = (for some C in Character => Some_Function (C))", only
15718 -- the first of the two uses of C should have a prefix added
15719 -- here; instead, both will get prefixes.
15721 if Nkind
(Parent
(N
)) /= N_Selected_Component
15722 or else N
/= Selector_Name
(Parent
(N
))
15724 Comp
:= Visible_Component
(Chars
(N
));
15726 if Present
(Comp
) then
15727 Add_Prefix
(N
, Comp
);
15733 -- Otherwise do the replacement if this is not a qualified
15734 -- reference to a homograph of the type itself. Note that the
15735 -- current instance could not appear in such a context, e.g.
15736 -- the prefix of a type conversion.
15739 if Nkind
(Parent
(N
)) /= N_Selected_Component
15740 or else N
/= Selector_Name
(Parent
(N
))
15742 Replace_Type_Reference
(N
);
15748 -- Case of selected component, which may be a subcomponent of the
15749 -- current instance, or an expanded name which is still unanalyzed.
15751 elsif Nkind
(N
) = N_Selected_Component
then
15753 -- If selector name is not our type, keep going (we might still
15754 -- have an occurrence of the type in the prefix). If it is a
15755 -- subcomponent of the current entity, add prefix.
15757 if Nkind
(Selector_Name
(N
)) /= N_Identifier
15758 or else Chars
(Selector_Name
(N
)) /= TName
15760 if Nkind
(Prefix
(N
)) = N_Identifier
then
15761 Comp
:= Visible_Component
(Chars
(Prefix
(N
)));
15763 if Present
(Comp
) then
15764 Add_Prefix
(Prefix
(N
), Comp
);
15770 -- Selector name is our type, check qualification
15773 -- Loop through scopes and prefixes, doing comparison
15775 Scop
:= Current_Scope
;
15776 Pref
:= Prefix
(N
);
15778 -- Continue if no more scopes or scope with no name
15780 if No
(Scop
) or else Nkind
(Scop
) not in N_Has_Chars
then
15784 -- Do replace if prefix is an identifier matching the scope
15785 -- that we are currently looking at.
15787 if Nkind
(Pref
) = N_Identifier
15788 and then Chars
(Pref
) = Chars
(Scop
)
15790 Replace_Type_Reference
(N
);
15794 -- Go check scope above us if prefix is itself of the form
15795 -- of a selected component, whose selector matches the scope
15796 -- we are currently looking at.
15798 if Nkind
(Pref
) = N_Selected_Component
15799 and then Nkind
(Selector_Name
(Pref
)) = N_Identifier
15800 and then Chars
(Selector_Name
(Pref
)) = Chars
(Scop
)
15802 Scop
:= Scope
(Scop
);
15803 Pref
:= Prefix
(Pref
);
15805 -- For anything else, we don't have a match, so keep on
15806 -- going, there are still some weird cases where we may
15807 -- still have a replacement within the prefix.
15815 -- Continue for any other node kind
15820 end Replace_Type_Ref
;
15822 procedure Replace_Type_Refs
is new Traverse_Proc
(Replace_Type_Ref
);
15824 -----------------------
15825 -- Visible_Component --
15826 -----------------------
15828 function Visible_Component
(Comp
: Name_Id
) return Entity_Id
is
15832 -- Types with nameable components are record, task, protected types
15834 if Ekind
(T
) in E_Record_Type | E_Task_Type | E_Protected_Type
then
15835 -- This is a sequential search, which seems acceptable
15836 -- efficiency-wise, given the typical size of component
15837 -- lists, protected operation lists, task item lists, and
15838 -- check expressions.
15840 E
:= First_Entity
(T
);
15841 while Present
(E
) loop
15842 if Comes_From_Source
(E
) and then Chars
(E
) = Comp
then
15849 -- Private discriminated types may have visible discriminants
15851 elsif Is_Private_Type
(T
) and then Has_Discriminants
(T
) then
15853 Decl
: constant Node_Id
:= Declaration_Node
(T
);
15858 -- Loop over the discriminants listed in the discriminant part
15859 -- of the private type declaration to find one with a matching
15860 -- name; then, if it exists, return the discriminant entity of
15861 -- the same name in the type, which is that of its full view.
15863 if Nkind
(Decl
) in N_Private_Extension_Declaration
15864 | N_Private_Type_Declaration
15865 and then Present
(Discriminant_Specifications
(Decl
))
15867 Discr
:= First
(Discriminant_Specifications
(Decl
));
15869 while Present
(Discr
) loop
15870 if Chars
(Defining_Identifier
(Discr
)) = Comp
then
15871 Discr
:= First_Discriminant
(T
);
15873 while Present
(Discr
) loop
15874 if Chars
(Discr
) = Comp
then
15878 Next_Discriminant
(Discr
);
15881 pragma Assert
(False);
15890 -- Nothing by that name
15893 end Visible_Component
;
15895 -- Start of processing for Replace_Type_References_Generic
15898 Replace_Type_Refs
(N
);
15899 end Replace_Type_References_Generic
;
15901 --------------------------------
15902 -- Resolve_Aspect_Expressions --
15903 --------------------------------
15905 procedure Resolve_Aspect_Expressions
(E
: Entity_Id
) is
15906 function Resolve_Name
(N
: Node_Id
) return Traverse_Result
;
15907 -- Verify that all identifiers in the expression, with the exception
15908 -- of references to the current entity, denote visible entities. This
15909 -- is done only to detect visibility errors, as the expression will be
15910 -- properly analyzed/expanded during analysis of the predicate function
15911 -- body. We omit quantified expressions from this test, given that they
15912 -- introduce a local identifier that would require proper expansion to
15913 -- handle properly.
15919 function Resolve_Name
(N
: Node_Id
) return Traverse_Result
is
15920 Dummy
: Traverse_Result
;
15923 if Nkind
(N
) = N_Selected_Component
then
15924 if Nkind
(Prefix
(N
)) = N_Identifier
15925 and then Chars
(Prefix
(N
)) /= Chars
(E
)
15927 Find_Selected_Component
(N
);
15932 -- Resolve identifiers that are not selectors in parameter
15933 -- associations (these are never resolved by visibility).
15935 elsif Nkind
(N
) = N_Identifier
15936 and then Chars
(N
) /= Chars
(E
)
15937 and then (Nkind
(Parent
(N
)) /= N_Parameter_Association
15938 or else N
/= Selector_Name
(Parent
(N
)))
15940 Find_Direct_Name
(N
);
15942 -- Reset the Entity if N is overloaded since the entity may not
15943 -- be the correct one.
15945 if Is_Overloaded
(N
) then
15946 Set_Entity
(N
, Empty
);
15949 -- The name in a component association needs no resolution
15951 elsif Nkind
(N
) = N_Component_Association
then
15952 Dummy
:= Resolve_Name
(Expression
(N
));
15955 elsif Nkind
(N
) = N_Quantified_Expression
then
15962 procedure Resolve_Aspect_Expression
is new Traverse_Proc
(Resolve_Name
);
15966 ASN
: Node_Id
:= First_Rep_Item
(E
);
15968 -- Start of processing for Resolve_Aspect_Expressions
15971 while Present
(ASN
) loop
15972 if Nkind
(ASN
) = N_Aspect_Specification
and then Entity
(ASN
) = E
then
15974 A_Id
: constant Aspect_Id
:= Get_Aspect_Id
(ASN
);
15975 Expr
: constant Node_Id
:= Expression
(ASN
);
15980 when Aspect_Aggregate
=>
15981 Resolve_Aspect_Aggregate
(Entity
(ASN
), Expr
);
15983 when Aspect_Stable_Properties
=>
15984 Resolve_Aspect_Stable_Properties
15985 (Entity
(ASN
), Expr
, Class_Present
(ASN
));
15987 when Aspect_Local_Restrictions
=>
15988 -- Expression is an aggregate, but only syntactically
15991 -- For now we only deal with aspects that do not generate
15992 -- subprograms, or that may mention current instances of
15993 -- types. These will require special handling???.
15995 when Aspect_Invariant
15996 | Aspect_Predicate_Failure
16000 when Aspect_Dynamic_Predicate
16001 | Aspect_Ghost_Predicate
16003 | Aspect_Static_Predicate
16005 -- Preanalyze expression after type replacement to catch
16006 -- name resolution errors if the predicate function has
16007 -- not been built yet.
16009 -- Note that we cannot use Preanalyze_Spec_Expression
16010 -- directly because of the special handling required for
16011 -- quantifiers (see comments on Resolve_Aspect_Expression
16012 -- above) but we need to emulate it properly.
16014 if No
(Predicate_Function
(E
)) then
16016 Save_In_Spec_Expression
: constant Boolean :=
16017 In_Spec_Expression
;
16018 Save_Full_Analysis
: constant Boolean :=
16021 In_Spec_Expression
:= True;
16022 Full_Analysis
:= False;
16023 Expander_Mode_Save_And_Set
(False);
16025 Resolve_Aspect_Expression
(Expr
);
16027 Expander_Mode_Restore
;
16028 Full_Analysis
:= Save_Full_Analysis
;
16029 In_Spec_Expression
:= Save_In_Spec_Expression
;
16033 when Pre_Post_Aspects
=>
16036 when Aspect_Iterable
=>
16037 if Nkind
(Expr
) = N_Aggregate
then
16042 Assoc
:= First
(Component_Associations
(Expr
));
16043 while Present
(Assoc
) loop
16044 if Nkind
(Expression
(Assoc
)) in N_Has_Entity
16046 Find_Direct_Name
(Expression
(Assoc
));
16054 -- The expression for Default_Value is a static expression
16055 -- of the type, but this expression does not freeze the
16056 -- type, so it can still appear in a representation clause
16057 -- before the actual freeze point.
16059 when Aspect_Default_Value
=>
16060 Set_Must_Not_Freeze
(Expr
);
16061 Preanalyze_Spec_Expression
(Expr
, E
);
16063 when Aspect_Priority
=>
16065 Preanalyze_Spec_Expression
(Expr
, Any_Integer
);
16068 -- Ditto for Storage_Size. Any other aspects that carry
16069 -- expressions that should not freeze ??? This is only
16070 -- relevant to the misuse of deferred constants.
16072 when Aspect_Storage_Size
=>
16073 Set_Must_Not_Freeze
(Expr
);
16074 Preanalyze_Spec_Expression
(Expr
, Any_Integer
);
16077 if Present
(Expr
) then
16078 case Aspect_Argument
(A_Id
) is
16080 | Optional_Expression
16082 Analyze_And_Resolve
(Expr
);
16087 if Nkind
(Expr
) = N_Identifier
then
16088 Find_Direct_Name
(Expr
);
16090 elsif Nkind
(Expr
) = N_Selected_Component
then
16091 Find_Selected_Component
(Expr
);
16099 Next_Rep_Item
(ASN
);
16101 end Resolve_Aspect_Expressions
;
16103 ----------------------------
16104 -- Parse_Aspect_Aggregate --
16105 ----------------------------
16107 procedure Parse_Aspect_Aggregate
16109 Empty_Subp
: in out Node_Id
;
16110 Add_Named_Subp
: in out Node_Id
;
16111 Add_Unnamed_Subp
: in out Node_Id
;
16112 New_Indexed_Subp
: in out Node_Id
;
16113 Assign_Indexed_Subp
: in out Node_Id
)
16115 Assoc
: Node_Id
:= First
(Component_Associations
(N
));
16120 while Present
(Assoc
) loop
16121 Subp
:= Expression
(Assoc
);
16122 Op_Name
:= Chars
(First
(Choices
(Assoc
)));
16123 if Op_Name
= Name_Empty
then
16124 Empty_Subp
:= Subp
;
16126 elsif Op_Name
= Name_Add_Named
then
16127 Add_Named_Subp
:= Subp
;
16129 elsif Op_Name
= Name_Add_Unnamed
then
16130 Add_Unnamed_Subp
:= Subp
;
16132 elsif Op_Name
= Name_New_Indexed
then
16133 New_Indexed_Subp
:= Subp
;
16135 elsif Op_Name
= Name_Assign_Indexed
then
16136 Assign_Indexed_Subp
:= Subp
;
16141 end Parse_Aspect_Aggregate
;
16143 -------------------------------------
16144 -- Parse_Aspect_Local_Restrictions --
16145 -------------------------------------
16147 function Parse_Aspect_Local_Restrictions
(Aspect_Spec
: Node_Id
)
16148 return Local_Restrict
.Local_Restriction_Set
16150 use Local_Restrict
;
16152 Result
: Local_Restriction_Set
:= (others => False);
16153 Id
: Node_Id
:= Expression
(Aspect_Spec
);
16154 Is_Agg
: constant Boolean := Nkind
(Id
) = N_Aggregate
16155 and then not Is_Empty_List
(Expressions
(Id
));
16158 Id
:= First
(Expressions
(Id
));
16161 while Present
(Id
) loop
16162 if Nkind
(Id
) /= N_Identifier
then
16163 Error_Msg_N
("local restriction name not an identifier", Id
);
16168 Found
: Boolean := False;
16169 Nam
: constant Name_Id
:= Chars
(Id
);
16171 for L_R
in Local_Restriction
loop
16173 S
: String := L_R
'Img;
16175 -- Note that the instance of System.Case_Util.To_Lower that
16178 -- function To_Lower (A : String) return String
16180 -- cannot be used here because it is not present in the
16181 -- run-time library used by the bootstrap compiler at the
16182 -- time of writing.
16184 if Length_Of_Name
(Nam
) = S
'Length
16185 and then Get_Name_String
(Nam
) = S
16187 if Result
(L_R
) then
16188 Error_Msg_N
("local restriction duplicated", Id
);
16192 Result
(L_R
) := True;
16199 Error_Msg_N
("invalid local restriction name", Id
);
16204 exit when not Is_Agg
;
16209 end Parse_Aspect_Local_Restrictions
;
16211 ------------------------------------
16212 -- Parse_Aspect_Stable_Properties --
16213 ------------------------------------
16215 function Parse_Aspect_Stable_Properties
16216 (Aspect_Spec
: Node_Id
; Negated
: out Boolean) return Subprogram_List
16218 function Extract_Entity
(Expr
: Node_Id
) return Entity_Id
;
16219 -- Given an element of a Stable_Properties aspect spec, return the
16220 -- associated entity.
16221 -- This function updates the Negated flag as a side effect.
16223 --------------------
16224 -- Extract_Entity --
16225 --------------------
16227 function Extract_Entity
(Expr
: Node_Id
) return Entity_Id
is
16230 if Nkind
(Expr
) = N_Op_Not
then
16232 Name
:= Right_Opnd
(Expr
);
16237 if Nkind
(Name
) in N_Has_Entity
then
16238 return Entity
(Name
);
16242 end Extract_Entity
;
16249 -- Start of processing for Parse_Aspect_Stable_Properties
16254 if Nkind
(Aspect_Spec
) /= N_Aggregate
then
16255 return (1 => Extract_Entity
(Aspect_Spec
));
16257 L
:= Expressions
(Aspect_Spec
);
16260 return Result
: Subprogram_List
(1 .. List_Length
(L
)) do
16261 for I
in Result
'Range loop
16262 Result
(I
) := Extract_Entity
(Id
);
16264 if No
(Result
(I
)) then
16265 pragma Assert
(Serious_Errors_Detected
> 0);
16266 goto Ignore_Aspect
;
16274 <<Ignore_Aspect
>> return (1 .. 0 => <>);
16275 end Parse_Aspect_Stable_Properties
;
16277 -------------------------------
16278 -- Validate_Aspect_Aggregate --
16279 -------------------------------
16281 procedure Validate_Aspect_Aggregate
(N
: Node_Id
) is
16282 Empty_Subp
: Node_Id
:= Empty
;
16283 Add_Named_Subp
: Node_Id
:= Empty
;
16284 Add_Unnamed_Subp
: Node_Id
:= Empty
;
16285 New_Indexed_Subp
: Node_Id
:= Empty
;
16286 Assign_Indexed_Subp
: Node_Id
:= Empty
;
16289 Error_Msg_Ada_2022_Feature
("aspect Aggregate", Sloc
(N
));
16291 if Nkind
(N
) /= N_Aggregate
16292 or else Present
(Expressions
(N
))
16293 or else No
(Component_Associations
(N
))
16295 Error_Msg_N
("aspect Aggregate requires an aggregate "
16296 & "with component associations", N
);
16300 Parse_Aspect_Aggregate
(N
,
16301 Empty_Subp
, Add_Named_Subp
, Add_Unnamed_Subp
,
16302 New_Indexed_Subp
, Assign_Indexed_Subp
);
16304 if No
(Empty_Subp
) then
16305 Error_Msg_N
("missing specification for Empty in aggregate", N
);
16308 if Present
(Add_Named_Subp
) then
16309 if Present
(Add_Unnamed_Subp
)
16310 or else Present
(Assign_Indexed_Subp
)
16313 ("conflicting operations for aggregate (RM 4.3.5)", N
);
16317 elsif No
(Add_Named_Subp
)
16318 and then No
(Add_Unnamed_Subp
)
16319 and then No
(Assign_Indexed_Subp
)
16321 Error_Msg_N
("incomplete specification for aggregate", N
);
16323 elsif Present
(New_Indexed_Subp
) /= Present
(Assign_Indexed_Subp
) then
16324 Error_Msg_N
("incomplete specification for indexed aggregate", N
);
16326 end Validate_Aspect_Aggregate
;
16328 -----------------------------------------
16329 -- Validate_Aspect_Local_Restrictions --
16330 -----------------------------------------
16332 procedure Validate_Aspect_Local_Restrictions
(E
: Entity_Id
; N
: Node_Id
) is
16333 use Local_Restrict
;
16335 -- Do not check Is_Parenthesis_Aggregate. We don't want to
16336 -- disallow the more familiar parens, but we also don't
16337 -- want to require parens for a homogeneous list.
16339 if Nkind
(N
) = N_Identifier
and then Paren_Count
(N
) = 1 then
16340 -- a positional aggregate with one element (in effect) is ok
16342 elsif Nkind
(N
) /= N_Aggregate
16343 or else No
(Expressions
(N
))
16344 or else Present
(Component_Associations
(N
))
16347 ("aspect Local_Restrictions requires a parenthesized list", N
);
16352 Set
: constant Local_Restriction_Set
16353 := Parse_Aspect_Local_Restrictions
(Parent
(N
));
16354 pragma Unreferenced
(Set
);
16359 -- This will be relaxed later, e.g. for generic subprograms or
16362 if Ekind
(E
) in Subprogram_Kind | E_Package
then
16363 if Get_Renamed_Entity
(E
) /= E
then
16365 ("aspect Local_Restrictions cannot be specified for "
16366 & "a renaming", N
);
16370 ("aspect Local_Restrictions can only be specified for "
16371 & "a subprogram or package spec", N
);
16373 end Validate_Aspect_Local_Restrictions
;
16375 ---------------------------------------
16376 -- Validate_Aspect_Stable_Properties --
16377 ---------------------------------------
16379 procedure Validate_Aspect_Stable_Properties
16380 (E
: Entity_Id
; N
: Node_Id
; Class_Present
: Boolean)
16382 Is_Aspect_Of_Type
: constant Boolean := Is_Type
(E
);
16384 type Permission
is (Forbidden
, Optional
, Required
);
16385 Modifier_Permission
: Permission
:=
16386 (if Is_Aspect_Of_Type
then Forbidden
else Optional
);
16387 Modifier_Error_Called
: Boolean := False;
16389 procedure Check_Property_Function_Arg
(PF_Arg
: Node_Id
);
16390 -- Check syntax of a property function argument
16392 ----------------------------------
16393 -- Check_Property_Function_Arg --
16394 ----------------------------------
16396 procedure Check_Property_Function_Arg
(PF_Arg
: Node_Id
) is
16397 procedure Modifier_Error
;
16398 -- Generate message about bad "not" modifier if no message already
16399 -- generated. Errors include specifying "not" for an aspect of
16400 -- of a type and specifying "not" for some but not all of the
16401 -- names in a list.
16403 --------------------
16404 -- Modifier_Error --
16405 --------------------
16407 procedure Modifier_Error
is
16409 if Modifier_Error_Called
then
16410 return; -- error message already generated
16413 Modifier_Error_Called
:= True;
16415 if Is_Aspect_Of_Type
then
16417 ("NOT modifier not allowed for Stable_Properties aspect"
16418 & " of a type", PF_Arg
);
16420 Error_Msg_N
("mixed use of NOT modifiers", PF_Arg
);
16422 end Modifier_Error
;
16424 PF_Name
: Node_Id
:= PF_Arg
;
16426 -- Start of processing for Check_Property_Function_Arg
16429 if Nkind
(PF_Arg
) = N_Op_Not
then
16430 PF_Name
:= Right_Opnd
(PF_Arg
);
16432 case Modifier_Permission
is
16436 Modifier_Permission
:= Required
;
16441 case Modifier_Permission
is
16445 Modifier_Permission
:= Forbidden
;
16451 if Nkind
(PF_Name
) not in
16452 N_Identifier | N_Operator_Symbol | N_Selected_Component
16454 Error_Msg_N
("bad property function name", PF_Name
);
16456 end Check_Property_Function_Arg
;
16458 -- Start of processing for Validate_Aspect_Stable_Properties
16461 Error_Msg_Ada_2022_Feature
("aspect Stable_Properties", Sloc
(N
));
16463 if not Is_Aspect_Of_Type
and then not Is_Subprogram
(E
) then
16464 Error_Msg_N
("Stable_Properties aspect can only be specified for "
16465 & "a type or a subprogram", N
);
16466 elsif Class_Present
then
16467 if Is_Aspect_Of_Type
then
16468 if not Is_Tagged_Type
(E
) then
16470 ("Stable_Properties''Class aspect cannot be specified for "
16471 & "an untagged type", N
);
16474 if not Is_Dispatching_Operation
(E
) then
16476 ("Stable_Properties''Class aspect cannot be specified for "
16477 & "a subprogram that is not a primitive subprogram "
16478 & "of a tagged type", N
);
16483 if Nkind
(N
) = N_Aggregate
then
16484 if Present
(Component_Associations
(N
))
16485 or else Null_Record_Present
(N
)
16486 or else No
(Expressions
(N
))
16488 Error_Msg_N
("bad Stable_Properties aspect specification", N
);
16493 PF_Arg
: Node_Id
:= First
(Expressions
(N
));
16495 while Present
(PF_Arg
) loop
16496 Check_Property_Function_Arg
(PF_Arg
);
16501 Check_Property_Function_Arg
(N
);
16503 end Validate_Aspect_Stable_Properties
;
16505 --------------------------------
16506 -- Resolve_Iterable_Operation --
16507 --------------------------------
16509 procedure Resolve_Iterable_Operation
16511 Cursor
: Entity_Id
;
16520 if not Is_Overloaded
(N
) then
16521 if not Is_Entity_Name
(N
)
16522 or else Ekind
(Entity
(N
)) /= E_Function
16523 or else Scope
(Entity
(N
)) /= Scope
(Typ
)
16524 or else No
(First_Formal
(Entity
(N
)))
16525 or else Etype
(First_Formal
(Entity
(N
))) /= Typ
16528 ("iterable primitive must be local function name whose first "
16529 & "formal is an iterable type", N
);
16534 F1
:= First_Formal
(Ent
);
16535 F2
:= Next_Formal
(F1
);
16537 if Nam
= Name_First
then
16539 -- First (Container) => Cursor
16541 if Etype
(Ent
) /= Cursor
then
16542 Error_Msg_N
("primitive for First must yield a cursor", N
);
16543 elsif Present
(F2
) then
16544 Error_Msg_N
("no match for First iterable primitive", N
);
16547 elsif Nam
= Name_Last
then
16549 -- Last (Container) => Cursor
16551 if Etype
(Ent
) /= Cursor
then
16552 Error_Msg_N
("primitive for Last must yield a cursor", N
);
16553 elsif Present
(F2
) then
16554 Error_Msg_N
("no match for Last iterable primitive", N
);
16557 elsif Nam
= Name_Next
then
16559 -- Next (Container, Cursor) => Cursor
16562 or else Etype
(F2
) /= Cursor
16563 or else Etype
(Ent
) /= Cursor
16564 or else Present
(Next_Formal
(F2
))
16566 Error_Msg_N
("no match for Next iterable primitive", N
);
16569 elsif Nam
= Name_Previous
then
16571 -- Previous (Container, Cursor) => Cursor
16574 or else Etype
(F2
) /= Cursor
16575 or else Etype
(Ent
) /= Cursor
16576 or else Present
(Next_Formal
(F2
))
16578 Error_Msg_N
("no match for Previous iterable primitive", N
);
16581 elsif Nam
= Name_Has_Element
then
16583 -- Has_Element (Container, Cursor) => Boolean
16586 or else Etype
(F2
) /= Cursor
16587 or else Etype
(Ent
) /= Standard_Boolean
16588 or else Present
(Next_Formal
(F2
))
16590 Error_Msg_N
("no match for Has_Element iterable primitive", N
);
16593 elsif Nam
= Name_Element
then
16595 -- Element (Container, Cursor) => Element_Type;
16598 or else Etype
(F2
) /= Cursor
16599 or else Present
(Next_Formal
(F2
))
16601 Error_Msg_N
("no match for Element iterable primitive", N
);
16605 raise Program_Error
;
16609 -- Overloaded case: find subprogram with proper signature. Caller
16610 -- will report error if no match is found.
16617 Get_First_Interp
(N
, I
, It
);
16618 while Present
(It
.Typ
) loop
16619 if Ekind
(It
.Nam
) = E_Function
16620 and then Scope
(It
.Nam
) = Scope
(Typ
)
16621 and then Present
(First_Formal
(It
.Nam
))
16622 and then Etype
(First_Formal
(It
.Nam
)) = Typ
16624 F1
:= First_Formal
(It
.Nam
);
16626 if Nam
= Name_First
then
16627 if Etype
(It
.Nam
) = Cursor
16628 and then No
(Next_Formal
(F1
))
16630 Set_Entity
(N
, It
.Nam
);
16634 elsif Nam
= Name_Next
then
16635 F2
:= Next_Formal
(F1
);
16638 and then No
(Next_Formal
(F2
))
16639 and then Etype
(F2
) = Cursor
16640 and then Etype
(It
.Nam
) = Cursor
16642 Set_Entity
(N
, It
.Nam
);
16646 elsif Nam
= Name_Has_Element
then
16647 F2
:= Next_Formal
(F1
);
16650 and then No
(Next_Formal
(F2
))
16651 and then Etype
(F2
) = Cursor
16652 and then Etype
(It
.Nam
) = Standard_Boolean
16654 Set_Entity
(N
, It
.Nam
);
16655 F2
:= Next_Formal
(F1
);
16659 elsif Nam
= Name_Element
then
16660 F2
:= Next_Formal
(F1
);
16663 and then No
(Next_Formal
(F2
))
16664 and then Etype
(F2
) = Cursor
16666 Set_Entity
(N
, It
.Nam
);
16672 Get_Next_Interp
(I
, It
);
16676 end Resolve_Iterable_Operation
;
16678 ------------------------------
16679 -- Resolve_Aspect_Aggregate --
16680 ------------------------------
16682 procedure Resolve_Aspect_Aggregate
16686 function Valid_Empty
(E
: Entity_Id
) return Boolean;
16687 function Valid_Add_Named
(E
: Entity_Id
) return Boolean;
16688 function Valid_Add_Unnamed
(E
: Entity_Id
) return Boolean;
16689 function Valid_New_Indexed
(E
: Entity_Id
) return Boolean;
16690 function Valid_Assign_Indexed
(E
: Entity_Id
) return Boolean;
16691 -- Predicates that establish the legality of each possible operation in
16692 -- an Aggregate aspect.
16695 with function Pred
(Id
: Node_Id
) return Boolean;
16696 procedure Resolve_Operation
(Subp_Id
: Node_Id
);
16697 -- Common processing to resolve each aggregate operation.
16699 ------------------------
16700 -- Valid_Assign_Index --
16701 ------------------------
16703 function Valid_Assign_Indexed
(E
: Entity_Id
) return Boolean is
16705 -- The profile must be the same as for Add_Named, with the added
16706 -- requirement that the key_type be a discrete type.
16708 if Valid_Add_Named
(E
) then
16709 return Is_Discrete_Type
(Etype
(Next_Formal
(First_Formal
(E
))));
16713 end Valid_Assign_Indexed
;
16719 function Valid_Empty
(E
: Entity_Id
) return Boolean is
16721 if Etype
(E
) /= Typ
or else Scope
(E
) /= Scope
(Typ
) then
16724 elsif Ekind
(E
) = E_Constant
then
16727 elsif Ekind
(E
) = E_Function
then
16728 return No
(First_Formal
(E
))
16730 (Is_Integer_Type
(Etype
(First_Formal
(E
)))
16731 and then No
(Next_Formal
(First_Formal
(E
))));
16737 ---------------------
16738 -- Valid_Add_Named --
16739 ---------------------
16741 function Valid_Add_Named
(E
: Entity_Id
) return Boolean is
16742 F2
, F3
: Entity_Id
;
16744 if Ekind
(E
) = E_Procedure
16745 and then Scope
(E
) = Scope
(Typ
)
16746 and then Number_Formals
(E
) = 3
16747 and then Etype
(First_Formal
(E
)) = Typ
16748 and then Ekind
(First_Formal
(E
)) = E_In_Out_Parameter
16750 F2
:= Next_Formal
(First_Formal
(E
));
16751 F3
:= Next_Formal
(F2
);
16752 return Ekind
(F2
) = E_In_Parameter
16753 and then Ekind
(F3
) = E_In_Parameter
16754 and then not Is_Limited_Type
(Etype
(F2
))
16755 and then not Is_Limited_Type
(Etype
(F3
));
16759 end Valid_Add_Named
;
16761 -----------------------
16762 -- Valid_Add_Unnamed --
16763 -----------------------
16765 function Valid_Add_Unnamed
(E
: Entity_Id
) return Boolean is
16767 return Ekind
(E
) = E_Procedure
16768 and then Scope
(E
) = Scope
(Typ
)
16769 and then Number_Formals
(E
) = 2
16770 and then Etype
(First_Formal
(E
)) = Typ
16771 and then Ekind
(First_Formal
(E
)) = E_In_Out_Parameter
16773 not Is_Limited_Type
(Etype
(Next_Formal
(First_Formal
(E
))));
16774 end Valid_Add_Unnamed
;
16776 -----------------------
16777 -- Valid_Nmw_Indexed --
16778 -----------------------
16780 function Valid_New_Indexed
(E
: Entity_Id
) return Boolean is
16782 return Ekind
(E
) = E_Function
16783 and then Scope
(E
) = Scope
(Typ
)
16784 and then Etype
(E
) = Typ
16785 and then Number_Formals
(E
) = 2
16786 and then Is_Discrete_Type
(Etype
(First_Formal
(E
)))
16787 and then Etype
(First_Formal
(E
)) =
16788 Etype
(Next_Formal
(First_Formal
(E
)));
16789 end Valid_New_Indexed
;
16791 -----------------------
16792 -- Resolve_Operation --
16793 -----------------------
16795 procedure Resolve_Operation
(Subp_Id
: Node_Id
) is
16802 if not Is_Overloaded
(Subp_Id
) then
16803 Subp
:= Entity
(Subp_Id
);
16804 if not Pred
(Subp
) then
16806 ("improper aggregate operation for&", Subp_Id
, Typ
);
16810 Set_Entity
(Subp_Id
, Empty
);
16811 Get_First_Interp
(Subp_Id
, I
, It
);
16812 while Present
(It
.Nam
) loop
16813 if Pred
(It
.Nam
) then
16814 Set_Is_Overloaded
(Subp_Id
, False);
16815 Set_Entity
(Subp_Id
, It
.Nam
);
16819 Get_Next_Interp
(I
, It
);
16822 if No
(Entity
(Subp_Id
)) then
16824 ("improper aggregate operation for&", Subp_Id
, Typ
);
16827 end Resolve_Operation
;
16833 procedure Resolve_Empty
is new Resolve_Operation
(Valid_Empty
);
16834 procedure Resolve_Unnamed
is new Resolve_Operation
(Valid_Add_Unnamed
);
16835 procedure Resolve_Named
is new Resolve_Operation
(Valid_Add_Named
);
16836 procedure Resolve_Indexed
is new Resolve_Operation
(Valid_New_Indexed
);
16837 procedure Resolve_Assign_Indexed
16838 is new Resolve_Operation
16839 (Valid_Assign_Indexed
);
16841 -- Start of processing for Resolve_Aspect_Aggregate
16844 Assoc
:= First
(Component_Associations
(Expr
));
16846 while Present
(Assoc
) loop
16847 Op_Name
:= Chars
(First
(Choices
(Assoc
)));
16849 -- When verifying the consistency of aspects between the freeze point
16850 -- and the end of declarations, we use a copy which is not analyzed
16851 -- yet, so do it now.
16853 Subp_Id
:= Expression
(Assoc
);
16854 if No
(Etype
(Subp_Id
)) then
16858 if Op_Name
= Name_Empty
then
16859 Resolve_Empty
(Subp_Id
);
16861 elsif Op_Name
= Name_Add_Named
then
16862 Resolve_Named
(Subp_Id
);
16864 elsif Op_Name
= Name_Add_Unnamed
then
16865 Resolve_Unnamed
(Subp_Id
);
16867 elsif Op_Name
= Name_New_Indexed
then
16868 Resolve_Indexed
(Subp_Id
);
16870 elsif Op_Name
= Name_Assign_Indexed
then
16871 Resolve_Assign_Indexed
(Subp_Id
);
16876 end Resolve_Aspect_Aggregate
;
16878 --------------------------------------
16879 -- Resolve_Aspect_Stable_Properties --
16880 --------------------------------------
16882 procedure Resolve_Aspect_Stable_Properties
16883 (Typ_Or_Subp
: Entity_Id
; Expr
: Node_Id
; Class_Present
: Boolean)
16885 Is_Aspect_Of_Type
: constant Boolean := Is_Type
(Typ_Or_Subp
);
16887 Singleton
: constant Boolean := Nkind
(Expr
) /= N_Aggregate
;
16888 Subp_Name
: Node_Id
:= (if Singleton
16890 else First
(Expressions
(Expr
)));
16893 if Is_Aspect_Of_Type
16894 and then Has_Private_Declaration
(Typ_Or_Subp
)
16895 and then not Is_Private_Type
(Typ_Or_Subp
)
16898 ("Stable_Properties aspect cannot be specified " &
16899 "for the completion of a private type", Typ_Or_Subp
);
16902 -- Analogous checks that the aspect is not specified for a completion
16903 -- in the subprogram case are not performed here because they are not
16904 -- specific to this particular aspect. Right ???
16907 Has_Not
:= Nkind
(Subp_Name
) = N_Op_Not
;
16909 Set_Analyzed
(Subp_Name
); -- ???
16910 Subp_Name
:= Right_Opnd
(Subp_Name
);
16913 if No
(Etype
(Subp_Name
)) then
16914 Analyze
(Subp_Name
);
16918 Subp
: Entity_Id
:= Empty
;
16923 function Is_Property_Function
(E
: Entity_Id
) return Boolean;
16924 -- Implements RM 7.3.4 definition of "property function"
16926 --------------------------
16927 -- Is_Property_Function --
16928 --------------------------
16930 function Is_Property_Function
(E
: Entity_Id
) return Boolean is
16932 if Ekind
(E
) not in E_Function | E_Operator
16933 or else Number_Formals
(E
) /= 1
16939 Param_Type
: constant Entity_Id
:=
16940 Base_Type
(Etype
(First_Formal
(E
)));
16942 function Matches_Param_Type
(Typ
: Entity_Id
)
16944 (Base_Type
(Typ
) = Param_Type
16946 (Is_Class_Wide_Type
(Param_Type
)
16947 and then Is_Ancestor
(Root_Type
(Param_Type
),
16948 Base_Type
(Typ
))));
16950 if Is_Aspect_Of_Type
then
16951 if Matches_Param_Type
(Typ_Or_Subp
) then
16954 elsif Is_Primitive
(Typ_Or_Subp
) then
16956 Formal
: Entity_Id
:= First_Formal
(Typ_Or_Subp
);
16958 while Present
(Formal
) loop
16959 if Matches_Param_Type
(Etype
(Formal
)) then
16961 -- Test whether Typ_Or_Subp (which is a subp
16962 -- in this case) is primitive op of the type
16963 -- of this parameter.
16964 if Scope
(Typ_Or_Subp
) = Scope
(Param_Type
) then
16968 Next_Formal
(Formal
);
16975 end Is_Property_Function
;
16977 if not Is_Overloaded
(Subp_Name
) then
16978 Subp
:= Entity
(Subp_Name
);
16979 if not Is_Property_Function
(Subp
) then
16980 Error_Msg_NE
("improper property function for&",
16981 Subp_Name
, Typ_Or_Subp
);
16985 Set_Entity
(Subp_Name
, Empty
);
16986 Get_First_Interp
(Subp_Name
, I
, It
);
16987 while Present
(It
.Nam
) loop
16988 if Is_Property_Function
(It
.Nam
) then
16989 if Present
(Subp
) then
16991 ("ambiguous property function name for&",
16992 Subp_Name
, Typ_Or_Subp
);
16997 Set_Is_Overloaded
(Subp_Name
, False);
16998 Set_Entity
(Subp_Name
, Subp
);
17001 Get_Next_Interp
(I
, It
);
17005 Error_Msg_NE
("improper property function for&",
17006 Subp_Name
, Typ_Or_Subp
);
17011 -- perform legality (as opposed to name resolution) Subp checks
17013 if Is_Limited_Type
(Etype
(Subp
)) then
17015 ("result type of property function for& is limited",
17016 Subp_Name
, Typ_Or_Subp
);
17019 if Ekind
(First_Formal
(Subp
)) /= E_In_Parameter
then
17021 ("mode of parameter of property function for& is not IN",
17022 Subp_Name
, Typ_Or_Subp
);
17025 if Is_Class_Wide_Type
(Etype
(First_Formal
(Subp
))) then
17026 if not Covers
(Etype
(First_Formal
(Subp
)), Typ_Or_Subp
) then
17028 ("class-wide parameter type of property function " &
17029 "for& does not cover the type",
17030 Subp_Name
, Typ_Or_Subp
);
17032 -- ??? This test is slightly stricter than 7.3.4(12/5);
17033 -- some legal corner cases may be incorrectly rejected.
17034 elsif Scope
(Subp
) /= Scope
(Etype
(First_Formal
(Subp
)))
17037 ("property function for& not declared in same scope " &
17038 "as parameter type",
17039 Subp_Name
, Typ_Or_Subp
);
17041 elsif Is_Aspect_Of_Type
and then
17042 Scope
(Subp
) /= Scope
(Typ_Or_Subp
) and then
17043 Scope
(Subp
) /= Standard_Standard
-- e.g., derived type's "abs"
17046 ("property function for& " &
17047 "not a primitive function of the type",
17048 Subp_Name
, Typ_Or_Subp
);
17052 -- check that Subp was mentioned in param type's aspect spec
17054 Param_Type
: constant Entity_Id
:=
17055 Base_Type
(Etype
(First_Formal
(Subp
)));
17056 Aspect_Spec
: constant Node_Id
:=
17057 Find_Value_Of_Aspect
17058 (Param_Type
, Aspect_Stable_Properties
,
17059 Class_Present
=> Class_Present
);
17060 Found
: Boolean := False;
17062 if Present
(Aspect_Spec
) then
17065 SPF_List
: constant Subprogram_List
:=
17066 Parse_Aspect_Stable_Properties
17067 (Aspect_Spec
, Negated
=> Ignored
);
17069 Found
:= (for some E
of SPF_List
=> E
= Subp
);
17070 -- look through renamings ???
17075 CW_Modifier
: constant String :=
17076 (if Class_Present
then "class-wide " else "");
17080 & "property function for& mentioned after NOT "
17083 & "stable property function of its parameter type",
17084 Subp_Name
, Typ_Or_Subp
);
17091 exit when Singleton
;
17093 Next
((if Has_Not
then Parent
(Subp_Name
) else Subp_Name
));
17094 exit when No
(Subp_Name
);
17097 Set_Analyzed
(Expr
);
17098 end Resolve_Aspect_Stable_Properties
;
17100 -----------------------------------------
17101 -- Resolve_Storage_Model_Type_Argument --
17102 -----------------------------------------
17104 procedure Resolve_Storage_Model_Type_Argument
17107 Addr_Type
: in out Entity_Id
;
17111 type Formal_Profile
is record
17113 Mode
: Formal_Kind
;
17116 type Formal_Profiles
is array (Positive range <>) of Formal_Profile
;
17118 function Aspect_Argument_Profile_Matches
17120 Profiles
: Formal_Profiles
;
17121 Result_Subt
: Entity_Id
;
17122 Err_On_Mismatch
: Boolean) return Boolean;
17123 -- Checks that the formal parameters of subprogram Subp conform to the
17124 -- subtypes and modes specified by Profiles, as well as to the result
17125 -- subtype Result_Subt when that is nonempty.
17127 function Aspect_Argument_Profile_Matches
17129 Profiles
: Formal_Profiles
;
17130 Result_Subt
: Entity_Id
;
17131 Err_On_Mismatch
: Boolean) return Boolean
17134 procedure Report_Argument_Error
17136 Formal
: Entity_Id
:= Empty
;
17137 Subt
: Entity_Id
:= Empty
);
17138 -- If Err_On_Mismatch is True, reports an argument error given by Msg
17139 -- associated with Formal and/or Subt.
17141 procedure Report_Argument_Error
17143 Formal
: Entity_Id
:= Empty
;
17144 Subt
: Entity_Id
:= Empty
)
17147 if Err_On_Mismatch
then
17148 if Present
(Formal
) then
17149 if Present
(Subt
) then
17150 Error_Msg_Node_2
:= Subt
;
17152 Error_Msg_NE
(Msg
, N
, Formal
);
17154 elsif Present
(Subt
) then
17155 Error_Msg_NE
(Msg
, N
, Subt
);
17158 Error_Msg_N
(Msg
, N
);
17161 end Report_Argument_Error
;
17165 Formal
: Entity_Id
:= First_Formal
(Subp
);
17166 Is_Error
: Boolean := False;
17168 -- Start of processing for Aspect_Argument_Profile_Matches
17171 for FP
of Profiles
loop
17172 if No
(Formal
) then
17174 Report_Argument_Error
("missing formal of }", Subt
=> FP
.Subt
);
17177 elsif not Subtypes_Statically_Match
17178 (Etype
(Formal
), FP
.Subt
)
17181 Report_Argument_Error
17182 ("formal& must be of subtype&",
17183 Formal
=> Formal
, Subt
=> FP
.Subt
);
17186 elsif Ekind
(Formal
) /= FP
.Mode
then
17188 Report_Argument_Error
17189 ("formal& has wrong mode", Formal
=> Formal
);
17193 Formal
:= Next_Formal
(Formal
);
17197 and then Present
(Formal
)
17200 Report_Argument_Error
17201 ("too many formals for subprogram in aspect");
17205 and then Present
(Result_Subt
)
17206 and then not Subtypes_Statically_Match
(Etype
(Subp
), Result_Subt
)
17209 Report_Argument_Error
17210 ("subprogram must have result}", Subt
=> Result_Subt
);
17213 return not Is_Error
;
17214 end Aspect_Argument_Profile_Matches
;
17220 Storage_Count_Type
: constant Entity_Id
:= RTE
(RE_Storage_Count
);
17221 System_Address_Type
: constant Entity_Id
:= RTE
(RE_Address
);
17223 -- Start of processing for Resolve_Storage_Model_Type_Argument
17226 if Nam
= Name_Address_Type
then
17227 if not Is_Entity_Name
(N
)
17228 or else not Is_Type
(Entity
(N
))
17229 or else (Root_Type
(Entity
(N
)) /= System_Address_Type
17230 and then not Is_Integer_Type
(Entity
(N
)))
17232 Error_Msg_N
("named entity must be a descendant of System.Address "
17233 & "or an integer type", N
);
17236 Addr_Type
:= Entity
(N
);
17240 -- If Addr_Type is not present as the first association, then we default
17241 -- it to System.Address.
17243 elsif No
(Addr_Type
) then
17244 Addr_Type
:= RTE
(RE_Address
);
17247 if Nam
= Name_Null_Address
then
17248 if not Is_Entity_Name
(N
)
17249 or else not Is_Constant_Object
(Entity
(N
))
17251 not Subtypes_Statically_Match
(Etype
(Entity
(N
)), Addr_Type
)
17254 ("named entity must be constant of subtype}", N
, Addr_Type
);
17259 elsif not Is_Overloaded
(N
) then
17260 if not Is_Entity_Name
(N
)
17261 or else Ekind
(Entity
(N
)) not in E_Function | E_Procedure
17262 or else Scope
(Entity
(N
)) /= Scope
(Typ
)
17264 Error_Msg_N
("argument must be local subprogram name", N
);
17270 if Nam
= Name_Allocate
then
17271 if not Aspect_Argument_Profile_Matches
17274 ((Typ
, E_In_Out_Parameter
),
17275 (Addr_Type
, E_Out_Parameter
),
17276 (Storage_Count_Type
, E_In_Parameter
),
17277 (Storage_Count_Type
, E_In_Parameter
)),
17278 Result_Subt
=> Empty
,
17279 Err_On_Mismatch
=> True)
17281 Error_Msg_N
("no match for Allocate operation", N
);
17284 elsif Nam
= Name_Deallocate
then
17285 if not Aspect_Argument_Profile_Matches
17288 ((Typ
, E_In_Out_Parameter
),
17289 (Addr_Type
, E_In_Parameter
),
17290 (Storage_Count_Type
, E_In_Parameter
),
17291 (Storage_Count_Type
, E_In_Parameter
)),
17292 Result_Subt
=> Empty
,
17293 Err_On_Mismatch
=> True)
17295 Error_Msg_N
("no match for Deallocate operation", N
);
17298 elsif Nam
= Name_Copy_From
then
17299 if not Aspect_Argument_Profile_Matches
17302 ((Typ
, E_In_Out_Parameter
),
17303 (System_Address_Type
, E_In_Parameter
),
17304 (Addr_Type
, E_In_Parameter
),
17305 (Storage_Count_Type
, E_In_Parameter
)),
17306 Result_Subt
=> Empty
,
17307 Err_On_Mismatch
=> True)
17309 Error_Msg_N
("no match for Copy_From operation", N
);
17312 elsif Nam
= Name_Copy_To
then
17313 if not Aspect_Argument_Profile_Matches
17316 ((Typ
, E_In_Out_Parameter
),
17317 (Addr_Type
, E_In_Parameter
),
17318 (System_Address_Type
, E_In_Parameter
),
17319 (Storage_Count_Type
, E_In_Parameter
)),
17320 Result_Subt
=> Empty
,
17321 Err_On_Mismatch
=> True)
17323 Error_Msg_N
("no match for Copy_To operation", N
);
17326 elsif Nam
= Name_Storage_Size
then
17327 if not Aspect_Argument_Profile_Matches
17329 Profiles
=> (1 => (Typ
, E_In_Parameter
)),
17330 Result_Subt
=> Storage_Count_Type
,
17331 Err_On_Mismatch
=> True)
17333 Error_Msg_N
("no match for Storage_Size operation", N
);
17337 null; -- Error will be caught in Validate_Storage_Model_Type_Aspect
17341 -- Overloaded case: find subprogram with proper signature
17346 Found_Match
: Boolean := False;
17349 Get_First_Interp
(N
, I
, It
);
17350 while Present
(It
.Typ
) loop
17351 if Ekind
(It
.Nam
) in E_Function | E_Procedure
17352 and then Scope
(It
.Nam
) = Scope
(Typ
)
17354 if Nam
= Name_Allocate
then
17356 Aspect_Argument_Profile_Matches
17359 ((Typ
, E_In_Out_Parameter
),
17360 (Addr_Type
, E_Out_Parameter
),
17361 (Storage_Count_Type
, E_In_Parameter
),
17362 (Storage_Count_Type
, E_In_Parameter
)),
17363 Result_Subt
=> Empty
,
17364 Err_On_Mismatch
=> False);
17366 elsif Nam
= Name_Deallocate
then
17368 Aspect_Argument_Profile_Matches
17371 ((Typ
, E_In_Out_Parameter
),
17372 (Addr_Type
, E_In_Parameter
),
17373 (Storage_Count_Type
, E_In_Parameter
),
17374 (Storage_Count_Type
, E_In_Parameter
)),
17375 Result_Subt
=> Empty
,
17376 Err_On_Mismatch
=> False);
17378 elsif Nam
= Name_Copy_From
then
17380 Aspect_Argument_Profile_Matches
17383 ((Typ
, E_In_Out_Parameter
),
17384 (System_Address_Type
, E_In_Parameter
),
17385 (Addr_Type
, E_In_Parameter
),
17386 (Storage_Count_Type
, E_In_Parameter
),
17387 (Storage_Count_Type
, E_In_Parameter
)),
17388 Result_Subt
=> Empty
,
17389 Err_On_Mismatch
=> False);
17391 elsif Nam
= Name_Copy_To
then
17393 Aspect_Argument_Profile_Matches
17396 ((Typ
, E_In_Out_Parameter
),
17397 (Addr_Type
, E_In_Parameter
),
17398 (Storage_Count_Type
, E_In_Parameter
),
17399 (System_Address_Type
, E_In_Parameter
),
17400 (Storage_Count_Type
, E_In_Parameter
)),
17401 Result_Subt
=> Empty
,
17402 Err_On_Mismatch
=> False);
17404 elsif Nam
= Name_Storage_Size
then
17406 Aspect_Argument_Profile_Matches
17408 Profiles
=> (1 => (Typ
, E_In_Parameter
)),
17409 Result_Subt
=> Storage_Count_Type
,
17410 Err_On_Mismatch
=> False);
17413 if Found_Match
then
17414 Set_Entity
(N
, It
.Nam
);
17419 Get_Next_Interp
(I
, It
);
17422 if not Found_Match
then
17424 ("no match found for Storage_Model_Type operation", N
);
17428 end Resolve_Storage_Model_Type_Argument
;
17434 procedure Set_Biased
17438 Biased
: Boolean := True)
17442 Set_Has_Biased_Representation
(E
);
17444 if Warn_On_Biased_Representation
then
17446 ("?.b?" & Msg
& " forces biased representation for&", N
, E
);
17451 --------------------
17452 -- Set_Enum_Esize --
17453 --------------------
17455 procedure Set_Enum_Esize
(T
: Entity_Id
) is
17461 -- Find the minimum standard size (8,16,32,64,128) that fits
17463 Lo
:= Enumeration_Rep
(Entity
(Type_Low_Bound
(T
)));
17464 Hi
:= Enumeration_Rep
(Entity
(Type_High_Bound
(T
)));
17467 if Lo
>= -Uint_2
**7 and then Hi
< Uint_2
**7 then
17468 Sz
:= UI_From_Int
(Standard_Character_Size
);
17469 -- Might be > 8 on some targets
17471 elsif Lo
>= -Uint_2
**15 and then Hi
< Uint_2
**15 then
17474 elsif Lo
>= -Uint_2
**31 and then Hi
< Uint_2
**31 then
17477 elsif Lo
>= -Uint_2
**63 and then Hi
< Uint_2
**63 then
17480 else pragma Assert
(Lo
>= -Uint_2
**127 and then Hi
< Uint_2
**127);
17485 if Hi
< Uint_2
**8 then
17486 Sz
:= UI_From_Int
(Standard_Character_Size
);
17488 elsif Hi
< Uint_2
**16 then
17491 elsif Hi
< Uint_2
**32 then
17494 elsif Hi
< Uint_2
**64 then
17497 else pragma Assert
(Hi
< Uint_2
**128);
17502 -- That minimum is the proper size unless we have a foreign convention
17503 -- and the size required is 32 or less, in which case we bump the size
17504 -- up to 32. This is required for C and C++ and seems reasonable for
17505 -- all other foreign conventions.
17507 if Has_Foreign_Convention
(T
)
17508 and then Esize
(T
) < Standard_Integer_Size
17510 -- Don't do this if Short_Enums on target
17512 and then not Target_Short_Enums
17514 Set_Esize
(T
, UI_From_Int
(Standard_Integer_Size
));
17518 end Set_Enum_Esize
;
17520 -----------------------------
17521 -- Uninstall_Discriminants --
17522 -----------------------------
17524 procedure Uninstall_Discriminants
(E
: Entity_Id
) is
17530 -- Discriminants have been made visible for type declarations and
17531 -- protected type declarations, not for subtype declarations.
17533 if Nkind
(Parent
(E
)) /= N_Subtype_Declaration
then
17534 Disc
:= First_Discriminant
(E
);
17535 while Present
(Disc
) loop
17536 if Disc
/= Current_Entity
(Disc
) then
17537 Prev
:= Current_Entity
(Disc
);
17538 while Present
(Prev
)
17539 and then Present
(Homonym
(Prev
))
17540 and then Homonym
(Prev
) /= Disc
17542 Prev
:= Homonym
(Prev
);
17548 Set_Is_Immediately_Visible
(Disc
, False);
17550 Outer
:= Homonym
(Disc
);
17551 while Present
(Outer
) and then Scope
(Outer
) = E
loop
17552 Outer
:= Homonym
(Outer
);
17555 -- Reset homonym link of other entities, but do not modify link
17556 -- between entities in current scope, so that the back end can
17557 -- have a proper count of local overloadings.
17560 Set_Name_Entity_Id
(Chars
(Disc
), Outer
);
17562 elsif Scope
(Prev
) /= Scope
(Disc
) then
17563 Set_Homonym
(Prev
, Outer
);
17566 Next_Discriminant
(Disc
);
17569 end Uninstall_Discriminants
;
17571 ------------------------------
17572 -- Validate_Address_Clauses --
17573 ------------------------------
17575 procedure Validate_Address_Clauses
is
17576 function Offset_Value
(Expr
: Node_Id
) return Uint
;
17577 -- Given an Address attribute reference, return the value in bits of its
17578 -- offset from the first bit of the underlying entity, or 0 if it is not
17579 -- known at compile time.
17585 function Offset_Value
(Expr
: Node_Id
) return Uint
is
17586 N
: Node_Id
:= Prefix
(Expr
);
17588 Val
: Uint
:= Uint_0
;
17591 -- Climb the prefix chain and compute the cumulative offset
17594 if Is_Entity_Name
(N
) then
17597 elsif Nkind
(N
) = N_Selected_Component
then
17598 Off
:= Component_Bit_Offset
(Entity
(Selector_Name
(N
)));
17599 if Present
(Off
) and then Off
>= Uint_0
then
17606 elsif Nkind
(N
) = N_Indexed_Component
then
17607 Off
:= Indexed_Component_Bit_Offset
(N
);
17608 if Present
(Off
) then
17621 -- Start of processing for Validate_Address_Clauses
17624 for J
in Address_Clause_Checks
.First
.. Address_Clause_Checks
.Last
loop
17626 ACCR
: Address_Clause_Check_Record
17627 renames Address_Clause_Checks
.Table
(J
);
17631 X_Alignment
: Uint
;
17632 Y_Alignment
: Uint
:= Uint_0
;
17635 Y_Size
: Uint
:= Uint_0
;
17640 -- Skip processing of this entry if warning already posted, or if
17641 -- alignments are not set.
17643 if not Address_Warning_Posted
(ACCR
.N
)
17644 and then Known_Alignment
(ACCR
.X
)
17645 and then Known_Alignment
(ACCR
.Y
)
17647 Expr
:= Original_Node
(Expression
(ACCR
.N
));
17649 -- Get alignments, sizes and offset, if any
17651 X_Alignment
:= Alignment
(ACCR
.X
);
17652 X_Size
:= Esize
(ACCR
.X
);
17654 if Present
(ACCR
.Y
) then
17655 Y_Alignment
:= Alignment
(ACCR
.Y
);
17657 (if Known_Esize
(ACCR
.Y
) then Esize
(ACCR
.Y
) else Uint_0
);
17661 and then Nkind
(Expr
) = N_Attribute_Reference
17662 and then Attribute_Name
(Expr
) = Name_Address
17664 X_Offs
:= Offset_Value
(Expr
);
17669 -- Check for known value not multiple of alignment
17671 if No
(ACCR
.Y
) then
17672 if not Alignment_Checks_Suppressed
(ACCR
)
17673 and then X_Alignment
/= 0
17674 and then ACCR
.A
mod X_Alignment
/= 0
17677 ("??specified address for& is inconsistent with "
17678 & "alignment", ACCR
.N
, ACCR
.X
);
17680 ("\??program execution may be erroneous (RM 13.3(27))",
17683 Error_Msg_Uint_1
:= X_Alignment
;
17684 Error_Msg_NE
("\??alignment of & is ^", ACCR
.N
, ACCR
.X
);
17687 -- Check for large object overlaying smaller one
17689 elsif Y_Size
> Uint_0
17690 and then X_Size
> Uint_0
17691 and then X_Offs
+ X_Size
> Y_Size
17693 Error_Msg_NE
("??& overlays smaller object", ACCR
.N
, ACCR
.X
);
17695 ("\??program execution may be erroneous", ACCR
.N
);
17697 Error_Msg_Uint_1
:= X_Size
;
17698 Error_Msg_NE
("\??size of & is ^", ACCR
.N
, ACCR
.X
);
17700 Error_Msg_Uint_1
:= Y_Size
;
17701 Error_Msg_NE
("\??size of & is ^", ACCR
.N
, ACCR
.Y
);
17703 if Y_Size
>= X_Size
then
17704 Error_Msg_Uint_1
:= X_Offs
;
17705 Error_Msg_NE
("\??but offset of & is ^", ACCR
.N
, ACCR
.X
);
17708 -- Check for inadequate alignment, both of the base object
17709 -- and of the offset, if any. We only do this check if the
17710 -- run-time Alignment_Check is active. No point in warning
17711 -- if this check has been suppressed (or is suppressed by
17712 -- default in the non-strict alignment machine case).
17714 -- Note: we do not check the alignment if we gave a size
17715 -- warning, since it would likely be redundant.
17717 elsif not Alignment_Checks_Suppressed
(ACCR
)
17718 and then Y_Alignment
/= Uint_0
17720 (Y_Alignment
< X_Alignment
17723 and then Nkind
(Expr
) = N_Attribute_Reference
17724 and then Attribute_Name
(Expr
) = Name_Address
17725 and then Has_Compatible_Alignment
17726 (ACCR
.X
, Prefix
(Expr
), True) /=
17730 ("??specified address for& may be inconsistent with "
17731 & "alignment", ACCR
.N
, ACCR
.X
);
17733 ("\??program execution may be erroneous (RM 13.3(27))",
17736 Error_Msg_Uint_1
:= X_Alignment
;
17737 Error_Msg_NE
("\??alignment of & is ^", ACCR
.N
, ACCR
.X
);
17739 Error_Msg_Uint_1
:= Y_Alignment
;
17740 Error_Msg_NE
("\??alignment of & is ^", ACCR
.N
, ACCR
.Y
);
17742 if Y_Alignment
>= X_Alignment
then
17744 ("\??but offset is not multiple of alignment", ACCR
.N
);
17750 end Validate_Address_Clauses
;
17752 ------------------------------
17753 -- Validate_Iterable_Aspect --
17754 ------------------------------
17756 procedure Validate_Iterable_Aspect
(Typ
: Entity_Id
; ASN
: Node_Id
) is
17757 Aggr
: constant Node_Id
:= Expression
(ASN
);
17762 Cursor
: Entity_Id
;
17764 First_Id
: Entity_Id
:= Empty
;
17765 Last_Id
: Entity_Id
:= Empty
;
17766 Next_Id
: Entity_Id
:= Empty
;
17767 Has_Element_Id
: Entity_Id
:= Empty
;
17768 Element_Id
: Entity_Id
:= Empty
;
17771 if Nkind
(Aggr
) /= N_Aggregate
then
17772 Error_Msg_N
("aspect Iterable must be an aggregate", Aggr
);
17776 Cursor
:= Get_Cursor_Type
(ASN
, Typ
);
17778 -- If previous error aspect is unusable
17780 if Cursor
= Any_Type
then
17784 if not Is_Empty_List
(Expressions
(Aggr
)) then
17786 ("illegal positional association", First
(Expressions
(Aggr
)));
17789 -- Each expression must resolve to a function with the proper signature
17791 Assoc
:= First
(Component_Associations
(Aggr
));
17792 while Present
(Assoc
) loop
17793 Expr
:= Expression
(Assoc
);
17796 Prim
:= First
(Choices
(Assoc
));
17798 if Nkind
(Prim
) /= N_Identifier
or else Present
(Next
(Prim
)) then
17799 Error_Msg_N
("illegal name in association", Prim
);
17801 elsif Chars
(Prim
) = Name_First
then
17802 Resolve_Iterable_Operation
(Expr
, Cursor
, Typ
, Name_First
);
17803 First_Id
:= Entity
(Expr
);
17805 elsif Chars
(Prim
) = Name_Last
then
17806 Resolve_Iterable_Operation
(Expr
, Cursor
, Typ
, Name_Last
);
17807 Last_Id
:= Entity
(Expr
);
17809 elsif Chars
(Prim
) = Name_Previous
then
17810 Resolve_Iterable_Operation
(Expr
, Cursor
, Typ
, Name_Previous
);
17811 Last_Id
:= Entity
(Expr
);
17813 elsif Chars
(Prim
) = Name_Next
then
17814 Resolve_Iterable_Operation
(Expr
, Cursor
, Typ
, Name_Next
);
17815 Next_Id
:= Entity
(Expr
);
17817 elsif Chars
(Prim
) = Name_Has_Element
then
17818 Resolve_Iterable_Operation
(Expr
, Cursor
, Typ
, Name_Has_Element
);
17819 Has_Element_Id
:= Entity
(Expr
);
17821 elsif Chars
(Prim
) = Name_Element
then
17822 Resolve_Iterable_Operation
(Expr
, Cursor
, Typ
, Name_Element
);
17823 Element_Id
:= Entity
(Expr
);
17826 Error_Msg_N
("invalid name for iterable function", Prim
);
17832 if No
(First_Id
) then
17833 Error_Msg_N
("match for First primitive not found", ASN
);
17835 elsif No
(Next_Id
) then
17836 Error_Msg_N
("match for Next primitive not found", ASN
);
17838 elsif No
(Has_Element_Id
) then
17839 Error_Msg_N
("match for Has_Element primitive not found", ASN
);
17841 elsif No
(Element_Id
) or else No
(Last_Id
) then
17844 end Validate_Iterable_Aspect
;
17846 ------------------------------
17847 -- Validate_Literal_Aspect --
17848 ------------------------------
17850 procedure Validate_Literal_Aspect
(Typ
: Entity_Id
; ASN
: Node_Id
) is
17851 A_Id
: constant Aspect_Id
:= Get_Aspect_Id
(ASN
);
17852 pragma Assert
(A_Id
in Aspect_Integer_Literal |
17853 Aspect_Real_Literal | Aspect_String_Literal
);
17854 Func_Name
: constant Node_Id
:= Expression
(ASN
);
17855 Overloaded
: Boolean := Is_Overloaded
(Func_Name
);
17857 I
: Interp_Index
:= 0;
17859 Param_Type
: Entity_Id
;
17860 Match_Found
: Boolean := False;
17861 Match2_Found
: Boolean := False;
17862 Is_Match
: Boolean;
17864 Match2
: Entity_Id
:= Empty
;
17867 (Param_Id
: Entity_Id
; Param_Type
: Entity_Id
) return Boolean;
17868 -- Return True if Param_Id is a non aliased in parameter whose base type
17876 (Param_Id
: Entity_Id
; Param_Type
: Entity_Id
) return Boolean is
17878 return Base_Type
(Etype
(Param_Id
)) = Param_Type
17879 and then Ekind
(Param_Id
) = E_In_Parameter
17880 and then not Is_Aliased
(Param_Id
);
17884 if not Is_Type
(Typ
) then
17885 Error_Msg_N
("aspect can only be specified for a type", ASN
);
17888 elsif not Is_First_Subtype
(Typ
) then
17889 Error_Msg_N
("aspect cannot be specified for a subtype", ASN
);
17893 if A_Id
= Aspect_String_Literal
then
17894 if Is_String_Type
(Typ
) then
17895 Error_Msg_N
("aspect cannot be specified for a string type", ASN
);
17899 Param_Type
:= Standard_Wide_Wide_String
;
17902 if Is_Numeric_Type
(Typ
) then
17903 Error_Msg_N
("aspect cannot be specified for a numeric type", ASN
);
17907 Param_Type
:= Standard_String
;
17910 if not Overloaded
and then No
(Entity
(Func_Name
)) then
17911 -- The aspect is specified by a subprogram name, which
17912 -- may be an operator name given originally by a string.
17914 if Is_Operator_Name
(Chars
(Func_Name
)) then
17915 Analyze_Operator_Symbol
(Func_Name
);
17917 Analyze
(Func_Name
);
17920 Overloaded
:= Is_Overloaded
(Func_Name
);
17924 Get_First_Interp
(Func_Name
, I
=> I
, It
=> It
);
17926 -- only one possible interpretation
17927 It
.Nam
:= Entity
(Func_Name
);
17928 pragma Assert
(Present
(It
.Nam
));
17931 while It
.Nam
/= Empty
loop
17934 if Ekind
(It
.Nam
) = E_Function
17935 and then Base_Type
(Etype
(It
.Nam
)) = Base_Type
(Typ
)
17938 Params
: constant List_Id
:=
17939 Parameter_Specifications
(Parent
(It
.Nam
));
17940 Param_Spec
: Node_Id
;
17943 if List_Length
(Params
) = 1 then
17944 Param_Spec
:= First
(Params
);
17946 Matching
(Defining_Identifier
(Param_Spec
), Param_Type
);
17948 -- Look for the optional overloaded 2-param Real_Literal
17950 elsif List_Length
(Params
) = 2
17951 and then A_Id
= Aspect_Real_Literal
17953 Param_Spec
:= First
(Params
);
17955 if Matching
(Defining_Identifier
(Param_Spec
), Param_Type
)
17957 Param_Spec
:= Next
(Param_Spec
);
17959 if Matching
(Defining_Identifier
(Param_Spec
), Param_Type
)
17961 if No
(Match2
) then
17963 Match2_Found
:= True;
17965 -- If we find more than one possible match then
17966 -- do not take any into account here: since the
17967 -- 2-parameter version of Real_Literal is optional
17968 -- we cannot generate an error here, so let
17969 -- standard resolution fail later if we do need to
17970 -- call this variant.
17972 Match2_Found
:= False;
17981 if Match_Found
then
17982 Error_Msg_N
("aspect specification is ambiguous", ASN
);
17986 Match_Found
:= True;
17990 exit when not Overloaded
;
17992 if not Is_Match
then
17993 Remove_Interp
(I
=> I
);
17996 Get_Next_Interp
(I
=> I
, It
=> It
);
17999 if not Match_Found
then
18001 ("function name in aspect specification cannot be resolved", ASN
);
18005 Set_Entity
(Func_Name
, Match
.Nam
);
18006 Set_Etype
(Func_Name
, Etype
(Match
.Nam
));
18007 Set_Is_Overloaded
(Func_Name
, False);
18009 -- Record the match for 2-parameter function if found
18011 if Match2_Found
then
18012 Set_Related_Expression
(Match
.Nam
, Match2
);
18014 end Validate_Literal_Aspect
;
18016 ----------------------------------------
18017 -- Validate_Storage_Model_Type_Aspect --
18018 ----------------------------------------
18020 procedure Validate_Storage_Model_Type_Aspect
18021 (Typ
: Entity_Id
; ASN
: Node_Id
)
18024 Choice
: Entity_Id
;
18025 Choice_Name
: Name_Id
;
18028 Address_Type_Id
: Entity_Id
:= Empty
;
18029 Null_Address_Id
: Entity_Id
:= Empty
;
18030 Allocate_Id
: Entity_Id
:= Empty
;
18031 Deallocate_Id
: Entity_Id
:= Empty
;
18032 Copy_From_Id
: Entity_Id
:= Empty
;
18033 Copy_To_Id
: Entity_Id
:= Empty
;
18034 Storage_Size_Id
: Entity_Id
:= Empty
;
18036 procedure Check_And_Resolve_Storage_Model_Type_Argument
18039 Argument_Id
: in out Entity_Id
;
18041 -- Checks that the subaspect for Nam has not already been specified for
18042 -- Typ's Storage_Model_Type aspect (i.e., checks Argument_Id = Empty),
18043 -- resolves Expr, and sets Argument_Id to the entity resolved for Expr.
18045 procedure Check_And_Resolve_Storage_Model_Type_Argument
18048 Argument_Id
: in out Entity_Id
;
18051 Name_String
: String := Get_Name_String
(Nam
);
18054 To_Mixed
(Name_String
);
18056 if Present
(Argument_Id
) then
18057 Error_Msg_String
(1 .. Name_String
'Length) := Name_String
;
18058 Error_Msg_Strlen
:= Name_String
'Length;
18060 Error_Msg_N
("~ already specified", Expr
);
18063 Resolve_Storage_Model_Type_Argument
(Expr
, Typ
, Address_Type_Id
, Nam
);
18064 Argument_Id
:= Entity
(Expr
);
18065 end Check_And_Resolve_Storage_Model_Type_Argument
;
18067 -- Start of processing for Validate_Storage_Model_Type_Aspect
18070 -- The aggregate argument of Storage_Model_Type is optional, and when
18071 -- not present the aspect defaults to the native storage model (where
18072 -- the address type is System.Address, and other arguments default to
18073 -- the corresponding native storage operations).
18075 if No
(Expression
(ASN
)) then
18079 -- Each expression must resolve to an entity of the right kind or proper
18082 Assoc
:= First
(Component_Associations
(Expression
(ASN
)));
18083 while Present
(Assoc
) loop
18084 Expr
:= Expression
(Assoc
);
18087 Choice
:= First
(Choices
(Assoc
));
18089 Choice_Name
:= Chars
(Choice
);
18091 if Nkind
(Choice
) /= N_Identifier
or else Present
(Next
(Choice
)) then
18092 Error_Msg_N
("illegal name in association", Choice
);
18094 elsif Choice_Name
= Name_Address_Type
then
18095 if Assoc
/= First
(Component_Associations
(Expression
(ASN
))) then
18096 Error_Msg_N
("Address_Type must be first association", Choice
);
18099 Check_And_Resolve_Storage_Model_Type_Argument
18100 (Expr
, Typ
, Address_Type_Id
, Name_Address_Type
);
18103 -- It's allowed to leave out the Address_Type argument, in which
18104 -- case the address type is defined to default to System.Address.
18106 if No
(Address_Type_Id
) then
18107 Address_Type_Id
:= RTE
(RE_Address
);
18110 if Choice_Name
= Name_Null_Address
then
18111 Check_And_Resolve_Storage_Model_Type_Argument
18112 (Expr
, Typ
, Null_Address_Id
, Name_Null_Address
);
18114 elsif Choice_Name
= Name_Allocate
then
18115 Check_And_Resolve_Storage_Model_Type_Argument
18116 (Expr
, Typ
, Allocate_Id
, Name_Allocate
);
18118 elsif Choice_Name
= Name_Deallocate
then
18119 Check_And_Resolve_Storage_Model_Type_Argument
18120 (Expr
, Typ
, Deallocate_Id
, Name_Deallocate
);
18122 elsif Choice_Name
= Name_Copy_From
then
18123 Check_And_Resolve_Storage_Model_Type_Argument
18124 (Expr
, Typ
, Copy_From_Id
, Name_Copy_From
);
18126 elsif Choice_Name
= Name_Copy_To
then
18127 Check_And_Resolve_Storage_Model_Type_Argument
18128 (Expr
, Typ
, Copy_To_Id
, Name_Copy_To
);
18130 elsif Choice_Name
= Name_Storage_Size
then
18131 Check_And_Resolve_Storage_Model_Type_Argument
18132 (Expr
, Typ
, Storage_Size_Id
, Name_Storage_Size
);
18136 ("invalid name for Storage_Model_Type argument", Choice
);
18143 -- If Address_Type has been specified as or defaults to System.Address,
18144 -- then other "subaspect" arguments can be specified, but are optional.
18145 -- Otherwise, all other arguments are required and an error is flagged
18146 -- about any that are missing.
18148 if Address_Type_Id
= RTE
(RE_Address
) then
18151 elsif No
(Null_Address_Id
) then
18152 Error_Msg_N
("match for Null_Address primitive not found", ASN
);
18154 elsif No
(Allocate_Id
) then
18155 Error_Msg_N
("match for Allocate primitive not found", ASN
);
18157 elsif No
(Deallocate_Id
) then
18158 Error_Msg_N
("match for Deallocate primitive not found", ASN
);
18160 elsif No
(Copy_From_Id
) then
18161 Error_Msg_N
("match for Copy_From primitive not found", ASN
);
18163 elsif No
(Copy_To_Id
) then
18164 Error_Msg_N
("match for Copy_To primitive not found", ASN
);
18166 elsif No
(Storage_Size_Id
) then
18167 Error_Msg_N
("match for Storage_Size primitive not found", ASN
);
18169 end Validate_Storage_Model_Type_Aspect
;
18171 -----------------------------------
18172 -- Validate_Unchecked_Conversion --
18173 -----------------------------------
18175 procedure Validate_Unchecked_Conversion
18177 Act_Unit
: Entity_Id
)
18179 Source
: Entity_Id
;
18180 Target
: Entity_Id
;
18182 procedure Warn_Nonportable
(RE
: RE_Id
);
18183 -- Warn if either source or target of the conversion is a predefined
18184 -- private type, whose representation might differ between releases and
18185 -- targets of the compiler.
18187 ----------------------
18188 -- Warn_Nonportable --
18189 ----------------------
18191 procedure Warn_Nonportable
(RE
: RE_Id
) is
18193 if Is_RTE
(Source
, RE
) or else Is_RTE
(Target
, RE
) then
18194 pragma Assert
(Is_Private_Type
(RTE
(RE
)));
18196 ("?z?representation of & values may change between "
18197 & "'G'N'A'T versions", N
, RTE
(RE
));
18199 end Warn_Nonportable
;
18205 -- Start of processing for Validate_Unchecked_Conversion
18208 -- Obtain source and target types. Note that we call Ancestor_Subtype
18209 -- here because the processing for generic instantiation always makes
18210 -- subtypes, and we want the original frozen actual types.
18212 Source
:= Ancestor_Subtype
(Etype
(First_Formal
(Act_Unit
)));
18213 Target
:= Ancestor_Subtype
(Etype
(Act_Unit
));
18215 -- If either type is generic, the instantiation happens within a generic
18216 -- unit, and there is nothing to check. The proper check will happen
18217 -- when the enclosing generic is instantiated.
18219 if Is_Generic_Type
(Source
) or else Is_Generic_Type
(Target
) then
18223 -- Warn if one of the operands is a private type declared in
18224 -- Ada.Calendar or Ada.Real_Time. Do not emit a warning when compiling
18225 -- GNAT-related sources.
18227 if Warn_On_Unchecked_Conversion
18228 and then not In_Predefined_Unit
(N
)
18230 Warn_Nonportable
(RO_CA_Time
);
18231 Warn_Nonportable
(RO_RT_Time
);
18232 Warn_Nonportable
(RE_Time_Span
);
18235 -- If we are dealing with private types, then do the check on their
18236 -- fully declared counterparts if the full declarations have been
18237 -- encountered (they don't have to be visible, but they must exist).
18239 if Is_Private_Type
(Source
)
18240 and then Present
(Underlying_Type
(Source
))
18242 Source
:= Underlying_Type
(Source
);
18245 if Is_Private_Type
(Target
)
18246 and then Present
(Underlying_Type
(Target
))
18248 Target
:= Underlying_Type
(Target
);
18251 -- Source may be unconstrained array, but not target, except in relaxed
18254 if Is_Array_Type
(Target
)
18255 and then not Is_Constrained
(Target
)
18256 and then not Relaxed_RM_Semantics
18259 ("unchecked conversion to unconstrained array not allowed", N
);
18263 -- Warn if conversion between two different convention pointers
18265 if Is_Access_Type
(Target
)
18266 and then Is_Access_Type
(Source
)
18267 and then Convention
(Target
) /= Convention
(Source
)
18268 and then Warn_On_Unchecked_Conversion
18270 -- Give warnings for subprogram pointers only on most targets
18272 if Is_Access_Subprogram_Type
(Target
)
18273 or else Is_Access_Subprogram_Type
(Source
)
18276 ("?z?conversion between pointers with different conventions!",
18281 -- Make entry in unchecked conversion table for later processing by
18282 -- Validate_Unchecked_Conversions, which will check sizes and alignments
18283 -- (using values set by the back end where possible). This is only done
18284 -- if the appropriate warning is active.
18286 if Warn_On_Unchecked_Conversion
then
18287 Unchecked_Conversions
.Append
18288 (New_Val
=> UC_Entry
'(Eloc => Sloc (N),
18291 Act_Unit => Act_Unit));
18293 -- If both sizes are known statically now, then back-end annotation
18294 -- is not required to do a proper check but if either size is not
18295 -- known statically, then we need the annotation.
18297 if Known_Static_RM_Size (Source)
18299 Known_Static_RM_Size (Target)
18303 Back_Annotate_Rep_Info := True;
18307 -- If unchecked conversion to access type, and access type is declared
18308 -- in the same unit as the unchecked conversion, then set the flag
18309 -- No_Strict_Aliasing (no strict aliasing is implicit here)
18311 if Is_Access_Type (Target)
18312 and then In_Same_Source_Unit (Target, N)
18314 Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
18317 -- If the unchecked conversion is between Address and an access
18318 -- subprogram type, show that we shouldn't use an internal
18319 -- representation for the access subprogram type.
18321 if Is_Access_Subprogram_Type (Target)
18322 and then Is_Descendant_Of_Address (Source)
18323 and then In_Same_Source_Unit (Target, N)
18325 Set_Can_Use_Internal_Rep (Base_Type (Target), False);
18326 elsif Is_Access_Subprogram_Type (Source)
18327 and then Is_Descendant_Of_Address (Target)
18328 and then In_Same_Source_Unit (Source, N)
18330 Set_Can_Use_Internal_Rep (Base_Type (Source), False);
18333 -- Generate N_Validate_Unchecked_Conversion node for back end in case
18334 -- the back end needs to perform special validation checks.
18336 -- Shouldn't this be in Exp_Ch13, since the check only gets done if we
18337 -- have full expansion and the back end is called ???
18340 Make_Validate_Unchecked_Conversion (Sloc (N));
18341 Set_Source_Type (Vnode, Source);
18342 Set_Target_Type (Vnode, Target);
18344 -- If the unchecked conversion node is in a list, just insert before it.
18345 -- If not we have some strange case, not worth bothering about.
18347 if Is_List_Member (N) then
18348 Insert_After (N, Vnode);
18350 end Validate_Unchecked_Conversion;
18352 ------------------------------------
18353 -- Validate_Unchecked_Conversions --
18354 ------------------------------------
18356 procedure Validate_Unchecked_Conversions is
18357 function Is_Null_Array (T : Entity_Id) return Boolean;
18358 -- We want to warn in the case of converting to a wrong-sized array of
18359 -- bytes, including the zero-size case. This returns True in that case,
18360 -- which is necessary because a size of 0 is used to indicate both an
18361 -- unknown size and a size of 0. It's OK for this to return True in
18362 -- other zero-size cases, but we don't go out of our way; for example,
18363 -- we don't bother with multidimensional arrays.
18365 function Is_Null_Array (T : Entity_Id) return Boolean is
18367 if Is_Array_Type (T) and then Is_Constrained (T) then
18369 Index : constant Node_Id := First_Index (T);
18370 R : Node_Id; -- N_Range
18372 case Nkind (Index) is
18375 when N_Subtype_Indication =>
18376 R := Range_Expression (Constraint (Index));
18377 when N_Identifier | N_Expanded_Name =>
18378 R := Scalar_Range (Entity (Index));
18380 raise Program_Error;
18383 return Is_Null_Range (Low_Bound (R), High_Bound (R));
18391 for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
18393 T : UC_Entry renames Unchecked_Conversions.Table (N);
18395 Act_Unit : constant Entity_Id := T.Act_Unit;
18396 Eloc : constant Source_Ptr := T.Eloc;
18397 Source : constant Entity_Id := T.Source;
18398 Target : constant Entity_Id := T.Target;
18404 -- Skip if function marked as warnings off
18406 if Has_Warnings_Off (Act_Unit)
18407 or else Serious_Errors_Detected > 0
18412 -- Don't do the check if warnings off for either type, note the
18413 -- deliberate use of OR here instead of OR ELSE to get the flag
18414 -- Warnings_Off_Used set for both types if appropriate.
18416 if Has_Warnings_Off (Source) or Has_Warnings_Off (Target) then
18420 if (Known_Static_RM_Size (Source)
18421 and then Known_Static_RM_Size (Target))
18422 or else Is_Null_Array (Target)
18424 -- This validation check, which warns if we have unequal sizes
18425 -- for unchecked conversion, and thus implementation dependent
18426 -- semantics, is one of the few occasions on which we use the
18427 -- official RM size instead of Esize. See description in Einfo
18428 -- "Handling of Type'Size Values" for details.
18430 Source_Siz := RM_Size (Source);
18431 Target_Siz := RM_Size (Target);
18433 if Present (Source_Siz) and then Present (Target_Siz)
18434 and then Source_Siz /= Target_Siz
18437 ("?z?types for unchecked conversion have different sizes!",
18440 if All_Errors_Mode then
18441 Error_Msg_Name_1 := Chars (Source);
18442 Error_Msg_Uint_1 := Source_Siz;
18443 Error_Msg_Name_2 := Chars (Target);
18444 Error_Msg_Uint_2 := Target_Siz;
18445 Error_Msg ("\size of % is ^, size of % is ^?z?", Eloc);
18447 Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
18449 if Is_Discrete_Type (Source)
18451 Is_Discrete_Type (Target)
18453 if Source_Siz > Target_Siz then
18455 ("\?z?^ high order bits of source will "
18456 & "be ignored!", Eloc);
18458 elsif Is_Unsigned_Type (Source) then
18460 ("\?z?source will be extended with ^ high order "
18461 & "zero bits!", Eloc);
18465 ("\?z?source will be extended with ^ high order "
18466 & "sign bits!", Eloc);
18469 elsif Source_Siz < Target_Siz then
18470 if Is_Discrete_Type (Target) then
18471 if Bytes_Big_Endian then
18473 ("\?z?target value will include ^ undefined "
18474 & "low order bits!", Eloc, Act_Unit);
18477 ("\?z?target value will include ^ undefined "
18478 & "high order bits!", Eloc, Act_Unit);
18483 ("\?z?^ trailing bits of target value will be "
18484 & "undefined!", Eloc, Act_Unit);
18487 else pragma Assert (Source_Siz > Target_Siz);
18488 if Is_Discrete_Type (Source) then
18489 if Bytes_Big_Endian then
18491 ("\?z?^ low order bits of source will be "
18492 & "ignored!", Eloc, Act_Unit);
18495 ("\?z?^ high order bits of source will be "
18496 & "ignored!", Eloc, Act_Unit);
18501 ("\?z?^ trailing bits of source will be "
18502 & "ignored!", Eloc, Act_Unit);
18509 -- If both types are access types, we need to check the alignment.
18510 -- If the alignment of both is specified, we can do it here.
18512 if Serious_Errors_Detected = 0
18513 and then Is_Access_Type (Source)
18514 and then Is_Access_Type (Target)
18515 and then Target_Strict_Alignment
18516 and then Present (Designated_Type (Source))
18517 and then Present (Designated_Type (Target))
18520 D_Source : constant Entity_Id := Designated_Type (Source);
18521 D_Target : constant Entity_Id := Designated_Type (Target);
18524 if Known_Alignment (D_Source)
18526 Known_Alignment (D_Target)
18529 Source_Align : constant Uint := Alignment (D_Source);
18530 Target_Align : constant Uint := Alignment (D_Target);
18533 if Source_Align < Target_Align
18534 and then not Is_Tagged_Type (D_Source)
18536 -- Suppress warning if warnings suppressed on either
18537 -- type or either designated type. Note the use of
18538 -- OR here instead of OR ELSE. That is intentional,
18539 -- we would like to set flag Warnings_Off_Used in
18540 -- all types for which warnings are suppressed.
18542 and then not (Has_Warnings_Off (D_Source)
18544 Has_Warnings_Off (D_Target)
18546 Has_Warnings_Off (Source)
18548 Has_Warnings_Off (Target))
18550 Error_Msg_Uint_1 := Target_Align;
18551 Error_Msg_Uint_2 := Source_Align;
18552 Error_Msg_Node_1 := D_Target;
18553 Error_Msg_Node_2 := D_Source;
18555 ("?z?alignment of & (^) is stricter than "
18556 & "alignment of & (^)!", Eloc, Act_Unit);
18558 ("\?z?resulting access value may have invalid "
18559 & "alignment!", Eloc, Act_Unit);
18570 end Validate_Unchecked_Conversions;
18573 User_Aspect_Support.Analyze_User_Aspect_Aspect_Specification_Hook :=
18574 Analyze_User_Aspect_Aspect_Specification'Access;