1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2021, 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 Aspects
; use Aspects
;
27 with Atree
; use Atree
;
28 with Checks
; use Checks
;
29 with Debug
; use Debug
;
30 with Einfo
; use Einfo
;
31 with Einfo
.Entities
; use Einfo
.Entities
;
32 with Einfo
.Utils
; use Einfo
.Utils
;
33 with Errout
; use Errout
;
34 with Expander
; use Expander
;
35 with Exp_Ch6
; use Exp_Ch6
;
36 with Exp_Tss
; use Exp_Tss
;
37 with Exp_Util
; use Exp_Util
;
38 with Freeze
; use Freeze
;
39 with Ghost
; use Ghost
;
41 with Lib
.Xref
; use Lib
.Xref
;
42 with Namet
; use Namet
;
43 with Nlists
; use Nlists
;
44 with Nmake
; use Nmake
;
47 with Sem_Aux
; use Sem_Aux
;
48 with Sem_Case
; use Sem_Case
;
49 with Sem_Ch3
; use Sem_Ch3
;
50 with Sem_Ch6
; use Sem_Ch6
;
51 with Sem_Ch8
; use Sem_Ch8
;
52 with Sem_Dim
; use Sem_Dim
;
53 with Sem_Disp
; use Sem_Disp
;
54 with Sem_Elab
; use Sem_Elab
;
55 with Sem_Eval
; use Sem_Eval
;
56 with Sem_Res
; use Sem_Res
;
57 with Sem_Type
; use Sem_Type
;
58 with Sem_Util
; use Sem_Util
;
59 with Sem_Warn
; use Sem_Warn
;
60 with Snames
; use Snames
;
61 with Stand
; use Stand
;
62 with Sinfo
; use Sinfo
;
63 with Sinfo
.Nodes
; use Sinfo
.Nodes
;
64 with Sinfo
.Utils
; use Sinfo
.Utils
;
65 with Targparm
; use Targparm
;
66 with Tbuild
; use Tbuild
;
67 with Ttypes
; use Ttypes
;
68 with Uintp
; use Uintp
;
70 package body Sem_Ch5
is
72 Current_Assignment
: Node_Id
:= Empty
;
73 -- This variable holds the node for an assignment that contains target
74 -- names. The corresponding flag has been set by the parser, and when
75 -- set the analysis of the RHS must be done with all expansion disabled,
76 -- because the assignment is reanalyzed after expansion has replaced all
77 -- occurrences of the target name appropriately.
79 Unblocked_Exit_Count
: Nat
:= 0;
80 -- This variable is used when processing if statements, case statements,
81 -- and block statements. It counts the number of exit points that are not
82 -- blocked by unconditional transfer instructions: for IF and CASE, these
83 -- are the branches of the conditional; for a block, they are the statement
84 -- sequence of the block, and the statement sequences of any exception
85 -- handlers that are part of the block. When processing is complete, if
86 -- this count is zero, it means that control cannot fall through the IF,
87 -- CASE or block statement. This is used for the generation of warning
88 -- messages. This variable is recursively saved on entry to processing the
89 -- construct, and restored on exit.
91 function Has_Sec_Stack_Call
(N
: Node_Id
) return Boolean;
92 -- N is the node for an arbitrary construct. This function searches the
93 -- construct N to see if any expressions within it contain function
94 -- calls that use the secondary stack, returning True if any such call
95 -- is found, and False otherwise.
97 procedure Preanalyze_Range
(R_Copy
: Node_Id
);
98 -- Determine expected type of range or domain of iteration of Ada 2012
99 -- loop by analyzing separate copy. Do the analysis and resolution of the
100 -- copy of the bound(s) with expansion disabled, to prevent the generation
101 -- of finalization actions. This prevents memory leaks when the bounds
102 -- contain calls to functions returning controlled arrays or when the
103 -- domain of iteration is a container.
105 ------------------------
106 -- Analyze_Assignment --
107 ------------------------
109 -- WARNING: This routine manages Ghost regions. Return statements must be
110 -- replaced by gotos which jump to the end of the routine and restore the
113 procedure Analyze_Assignment
(N
: Node_Id
) is
114 Lhs
: constant Node_Id
:= Name
(N
);
115 Rhs
: Node_Id
:= Expression
(N
);
117 procedure Diagnose_Non_Variable_Lhs
(N
: Node_Id
);
118 -- N is the node for the left hand side of an assignment, and it is not
119 -- a variable. This routine issues an appropriate diagnostic.
121 function Is_Protected_Part_Of_Constituent
122 (Nod
: Node_Id
) return Boolean;
123 -- Determine whether arbitrary node Nod denotes a Part_Of constituent of
124 -- a single protected type.
127 -- This is called to kill current value settings of a simple variable
128 -- on the left hand side. We call it if we find any error in analyzing
129 -- the assignment, and at the end of processing before setting any new
130 -- current values in place.
132 procedure Set_Assignment_Type
134 Opnd_Type
: in out Entity_Id
);
135 -- Opnd is either the Lhs or Rhs of the assignment, and Opnd_Type is the
136 -- nominal subtype. This procedure is used to deal with cases where the
137 -- nominal subtype must be replaced by the actual subtype.
139 procedure Transform_BIP_Assignment
(Typ
: Entity_Id
);
140 function Should_Transform_BIP_Assignment
141 (Typ
: Entity_Id
) return Boolean;
142 -- If the right-hand side of an assignment statement is a build-in-place
143 -- call we cannot build in place, so we insert a temp initialized with
144 -- the call, and transform the assignment statement to copy the temp.
145 -- Transform_BIP_Assignment does the tranformation, and
146 -- Should_Transform_BIP_Assignment determines whether we should.
147 -- The same goes for qualified expressions and conversions whose
148 -- operand is such a call.
150 -- This is only for nonlimited types; assignment statements are illegal
151 -- for limited types, but are generated internally for aggregates and
152 -- init procs. These limited-type are not really assignment statements
153 -- -- conceptually, they are initializations, so should not be
156 -- Similarly, for nonlimited types, aggregates and init procs generate
157 -- assignment statements that are really initializations. These are
158 -- marked No_Ctrl_Actions.
160 function Within_Function
return Boolean;
161 -- Determine whether the current scope is a function or appears within
164 -------------------------------
165 -- Diagnose_Non_Variable_Lhs --
166 -------------------------------
168 procedure Diagnose_Non_Variable_Lhs
(N
: Node_Id
) is
170 -- Not worth posting another error if left hand side already flagged
171 -- as being illegal in some respect.
173 if Error_Posted
(N
) then
176 -- Some special bad cases of entity names
178 elsif Is_Entity_Name
(N
) then
180 Ent
: constant Entity_Id
:= Entity
(N
);
183 if Ekind
(Ent
) = E_Loop_Parameter
184 or else Is_Loop_Parameter
(Ent
)
186 Error_Msg_N
("assignment to loop parameter not allowed", N
);
189 elsif Ekind
(Ent
) = E_In_Parameter
then
191 ("assignment to IN mode parameter not allowed", N
);
194 -- Renamings of protected private components are turned into
195 -- constants when compiling a protected function. In the case
196 -- of single protected types, the private component appears
199 elsif (Is_Prival
(Ent
) and then Within_Function
)
200 or else Is_Protected_Component
(Ent
)
203 ("protected function cannot modify its protected object",
209 -- For indexed components, test prefix if it is in array. We do not
210 -- want to recurse for cases where the prefix is a pointer, since we
211 -- may get a message confusing the pointer and what it references.
213 elsif Nkind
(N
) = N_Indexed_Component
214 and then Is_Array_Type
(Etype
(Prefix
(N
)))
216 Diagnose_Non_Variable_Lhs
(Prefix
(N
));
219 -- Another special case for assignment to discriminant
221 elsif Nkind
(N
) = N_Selected_Component
then
222 if Present
(Entity
(Selector_Name
(N
)))
223 and then Ekind
(Entity
(Selector_Name
(N
))) = E_Discriminant
225 Error_Msg_N
("assignment to discriminant not allowed", N
);
228 -- For selection from record, diagnose prefix, but note that again
229 -- we only do this for a record, not e.g. for a pointer.
231 elsif Is_Record_Type
(Etype
(Prefix
(N
))) then
232 Diagnose_Non_Variable_Lhs
(Prefix
(N
));
237 -- If we fall through, we have no special message to issue
239 Error_Msg_N
("left hand side of assignment must be a variable", N
);
240 end Diagnose_Non_Variable_Lhs
;
242 --------------------------------------
243 -- Is_Protected_Part_Of_Constituent --
244 --------------------------------------
246 function Is_Protected_Part_Of_Constituent
247 (Nod
: Node_Id
) return Boolean
249 Encap_Id
: Entity_Id
;
253 -- Abstract states and variables may act as Part_Of constituents of
254 -- single protected types, however only variables can be modified by
257 if Is_Entity_Name
(Nod
) then
258 Var_Id
:= Entity
(Nod
);
260 if Present
(Var_Id
) and then Ekind
(Var_Id
) = E_Variable
then
261 Encap_Id
:= Encapsulating_State
(Var_Id
);
263 -- To qualify, the node must denote a reference to a variable
264 -- whose encapsulating state is a single protected object.
268 and then Is_Single_Protected_Object
(Encap_Id
);
273 end Is_Protected_Part_Of_Constituent
;
279 procedure Kill_Lhs
is
281 if Is_Entity_Name
(Lhs
) then
283 Ent
: constant Entity_Id
:= Entity
(Lhs
);
285 if Present
(Ent
) then
286 Kill_Current_Values
(Ent
);
292 -------------------------
293 -- Set_Assignment_Type --
294 -------------------------
296 procedure Set_Assignment_Type
298 Opnd_Type
: in out Entity_Id
)
303 Require_Entity
(Opnd
);
305 -- If the assignment operand is an in-out or out parameter, then we
306 -- get the actual subtype (needed for the unconstrained case). If the
307 -- operand is the actual in an entry declaration, then within the
308 -- accept statement it is replaced with a local renaming, which may
309 -- also have an actual subtype.
311 if Is_Entity_Name
(Opnd
)
312 and then (Ekind
(Entity
(Opnd
)) in E_Out_Parameter
314 | E_Generic_In_Out_Parameter
316 (Ekind
(Entity
(Opnd
)) = E_Variable
317 and then Nkind
(Parent
(Entity
(Opnd
))) =
318 N_Object_Renaming_Declaration
319 and then Nkind
(Parent
(Parent
(Entity
(Opnd
)))) =
322 Opnd_Type
:= Get_Actual_Subtype
(Opnd
);
324 -- If assignment operand is a component reference, then we get the
325 -- actual subtype of the component for the unconstrained case.
327 elsif Nkind
(Opnd
) in N_Selected_Component | N_Explicit_Dereference
328 and then not Is_Unchecked_Union
(Opnd_Type
)
330 Decl
:= Build_Actual_Subtype_Of_Component
(Opnd_Type
, Opnd
);
332 if Present
(Decl
) then
333 Insert_Action
(N
, Decl
);
334 Mark_Rewrite_Insertion
(Decl
);
336 Opnd_Type
:= Defining_Identifier
(Decl
);
337 Set_Etype
(Opnd
, Opnd_Type
);
338 Freeze_Itype
(Opnd_Type
, N
);
340 elsif Is_Constrained
(Etype
(Opnd
)) then
341 Opnd_Type
:= Etype
(Opnd
);
344 -- For slice, use the constrained subtype created for the slice
346 elsif Nkind
(Opnd
) = N_Slice
then
347 Opnd_Type
:= Etype
(Opnd
);
349 end Set_Assignment_Type
;
351 -------------------------------------
352 -- Should_Transform_BIP_Assignment --
353 -------------------------------------
355 function Should_Transform_BIP_Assignment
356 (Typ
: Entity_Id
) return Boolean
360 and then not Is_Limited_View
(Typ
)
361 and then Is_Build_In_Place_Result_Type
(Typ
)
362 and then not No_Ctrl_Actions
(N
)
364 -- This function is called early, before name resolution is
365 -- complete, so we have to deal with things that might turn into
366 -- function calls later. N_Function_Call and N_Op nodes are the
367 -- obvious case. An N_Identifier or N_Expanded_Name is a
368 -- parameterless function call if it denotes a function.
369 -- Finally, an attribute reference can be a function call.
372 Unqual_Rhs
: constant Node_Id
:= Unqual_Conv
(Rhs
);
374 case Nkind
(Unqual_Rhs
) is
384 Ekind
(Entity
(Unqual_Rhs
)) in E_Function | E_Operator
;
386 -- T'Input will turn into a call whose result type is T
388 when N_Attribute_Reference
=>
389 return Attribute_Name
(Unqual_Rhs
) = Name_Input
;
398 end Should_Transform_BIP_Assignment
;
400 ------------------------------
401 -- Transform_BIP_Assignment --
402 ------------------------------
404 procedure Transform_BIP_Assignment
(Typ
: Entity_Id
) is
406 -- Tranform "X : [constant] T := F (...);" into:
408 -- Temp : constant T := F (...);
411 Loc
: constant Source_Ptr
:= Sloc
(N
);
412 Def_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'Y', Rhs
);
413 Obj_Decl
: constant Node_Id
:=
414 Make_Object_Declaration
(Loc
,
415 Defining_Identifier
=> Def_Id
,
416 Constant_Present
=> True,
417 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
419 Has_Init_Expression
=> True);
422 Set_Etype
(Def_Id
, Typ
);
423 Set_Expression
(N
, New_Occurrence_Of
(Def_Id
, Loc
));
425 -- At this point, Rhs is no longer equal to Expression (N), so:
427 Rhs
:= Expression
(N
);
429 Insert_Action
(N
, Obj_Decl
);
430 end Transform_BIP_Assignment
;
432 ---------------------
433 -- Within_Function --
434 ---------------------
436 function Within_Function
return Boolean is
437 Scop_Id
: constant Entity_Id
:= Current_Scope
;
440 if Ekind
(Scop_Id
) = E_Function
then
443 elsif Ekind
(Enclosing_Dynamic_Scope
(Scop_Id
)) = E_Function
then
452 Saved_GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
453 Saved_IGR
: constant Node_Id
:= Ignored_Ghost_Region
;
454 -- Save the Ghost-related attributes to restore on exit
459 Save_Full_Analysis
: Boolean := False;
460 -- Force initialization to facilitate static analysis
462 -- Start of processing for Analyze_Assignment
465 Mark_Coextensions
(N
, Rhs
);
467 -- Preserve relevant elaboration-related attributes of the context which
468 -- are no longer available or very expensive to recompute once analysis,
469 -- resolution, and expansion are over.
471 Mark_Elaboration_Attributes
476 -- An assignment statement is Ghost when the left hand side denotes a
477 -- Ghost entity. Set the mode now to ensure that any nodes generated
478 -- during analysis and expansion are properly marked as Ghost.
480 Mark_And_Set_Ghost_Assignment
(N
);
482 if Has_Target_Names
(N
) then
483 pragma Assert
(No
(Current_Assignment
));
484 Current_Assignment
:= N
;
485 Expander_Mode_Save_And_Set
(False);
486 Save_Full_Analysis
:= Full_Analysis
;
487 Full_Analysis
:= False;
493 -- Ensure that we never do an assignment on a variable marked as
494 -- Is_Safe_To_Reevaluate.
497 (not Is_Entity_Name
(Lhs
)
498 or else Ekind
(Entity
(Lhs
)) /= E_Variable
499 or else not Is_Safe_To_Reevaluate
(Entity
(Lhs
)));
501 -- Start type analysis for assignment
505 -- In the most general case, both Lhs and Rhs can be overloaded, and we
506 -- must compute the intersection of the possible types on each side.
508 if Is_Overloaded
(Lhs
) then
515 Get_First_Interp
(Lhs
, I
, It
);
517 while Present
(It
.Typ
) loop
519 -- An indexed component with generalized indexing is always
520 -- overloaded with the corresponding dereference. Discard the
521 -- interpretation that yields a reference type, which is not
524 if Nkind
(Lhs
) = N_Indexed_Component
525 and then Present
(Generalized_Indexing
(Lhs
))
526 and then Has_Implicit_Dereference
(It
.Typ
)
530 -- This may be a call to a parameterless function through an
531 -- implicit dereference, so discard interpretation as well.
533 elsif Is_Entity_Name
(Lhs
)
534 and then Has_Implicit_Dereference
(It
.Typ
)
538 elsif Has_Compatible_Type
(Rhs
, It
.Typ
) then
539 if T1
= Any_Type
then
542 -- An explicit dereference is overloaded if the prefix
543 -- is. Try to remove the ambiguity on the prefix, the
544 -- error will be posted there if the ambiguity is real.
546 if Nkind
(Lhs
) = N_Explicit_Dereference
then
549 PI1
: Interp_Index
:= 0;
555 Get_First_Interp
(Prefix
(Lhs
), PI
, PIt
);
557 while Present
(PIt
.Typ
) loop
558 if Is_Access_Type
(PIt
.Typ
)
559 and then Has_Compatible_Type
560 (Rhs
, Designated_Type
(PIt
.Typ
))
564 Disambiguate
(Prefix
(Lhs
),
567 if PIt
= No_Interp
then
569 ("ambiguous left-hand side in "
570 & "assignment", Lhs
);
573 Resolve
(Prefix
(Lhs
), PIt
.Typ
);
583 Get_Next_Interp
(PI
, PIt
);
589 ("ambiguous left-hand side in assignment", Lhs
);
595 Get_Next_Interp
(I
, It
);
599 if T1
= Any_Type
then
601 ("no valid types for left-hand side for assignment", Lhs
);
607 -- Deal with build-in-place calls for nonlimited types. We don't do this
608 -- later, because resolving the rhs tranforms it incorrectly for build-
611 if Should_Transform_BIP_Assignment
(Typ
=> T1
) then
613 -- In certain cases involving user-defined concatenation operators,
614 -- we need to resolve the right-hand side before transforming the
617 case Nkind
(Unqual_Conv
(Rhs
)) is
618 when N_Function_Call
=>
621 First
(Parameter_Associations
(Unqual_Conv
(Rhs
)));
622 Actual_Exp
: Node_Id
;
625 while Present
(Actual
) loop
626 if Nkind
(Actual
) = N_Parameter_Association
then
627 Actual_Exp
:= Explicit_Actual_Parameter
(Actual
);
629 Actual_Exp
:= Actual
;
632 if Nkind
(Actual_Exp
) = N_Op_Concat
then
641 when N_Attribute_Reference
652 Transform_BIP_Assignment
(Typ
=> T1
);
655 pragma Assert
(not Should_Transform_BIP_Assignment
(Typ
=> T1
));
657 -- The resulting assignment type is T1, so now we will resolve the left
658 -- hand side of the assignment using this determined type.
662 -- Cases where Lhs is not a variable. In an instance or an inlined body
663 -- no need for further check because assignment was legal in template.
665 if In_Inlined_Body
then
668 elsif not Is_Variable
(Lhs
) then
670 -- Ada 2005 (AI-327): Check assignment to the attribute Priority of a
678 if Ada_Version
>= Ada_2005
then
680 -- Handle chains of renamings
683 while Nkind
(Ent
) in N_Has_Entity
684 and then Present
(Entity
(Ent
))
685 and then Is_Object
(Entity
(Ent
))
686 and then Present
(Renamed_Object
(Entity
(Ent
)))
688 Ent
:= Renamed_Object
(Entity
(Ent
));
691 if (Nkind
(Ent
) = N_Attribute_Reference
692 and then Attribute_Name
(Ent
) = Name_Priority
)
694 -- Renamings of the attribute Priority applied to protected
695 -- objects have been previously expanded into calls to the
696 -- Get_Ceiling run-time subprogram.
698 or else Is_Expanded_Priority_Attribute
(Ent
)
700 -- The enclosing subprogram cannot be a protected function
703 while not (Is_Subprogram
(S
)
704 and then Convention
(S
) = Convention_Protected
)
705 and then S
/= Standard_Standard
710 if Ekind
(S
) = E_Function
711 and then Convention
(S
) = Convention_Protected
714 ("protected function cannot modify its protected " &
719 -- Changes of the ceiling priority of the protected object
720 -- are only effective if the Ceiling_Locking policy is in
721 -- effect (AARM D.5.2 (5/2)).
723 if Locking_Policy
/= 'C' then
725 ("assignment to the attribute PRIORITY has no effect??",
728 ("\since no Locking_Policy has been specified??", Lhs
);
736 Diagnose_Non_Variable_Lhs
(Lhs
);
739 -- Error of assigning to limited type. We do however allow this in
740 -- certain cases where the front end generates the assignments.
742 elsif Is_Limited_Type
(T1
)
743 and then not Assignment_OK
(Lhs
)
744 and then not Assignment_OK
(Original_Node
(Lhs
))
746 -- CPP constructors can only be called in declarations
748 if Is_CPP_Constructor_Call
(Rhs
) then
749 Error_Msg_N
("invalid use of 'C'P'P constructor", Rhs
);
752 ("left hand of assignment must not be limited type", Lhs
);
753 Explain_Limited_Type
(T1
, Lhs
);
758 -- A class-wide type may be a limited view. This illegal case is not
759 -- caught by previous checks.
761 elsif Ekind
(T1
) = E_Class_Wide_Type
and then From_Limited_With
(T1
) then
762 Error_Msg_NE
("invalid use of limited view of&", Lhs
, T1
);
765 -- Enforce RM 3.9.3 (8): the target of an assignment operation cannot be
766 -- abstract. This is only checked when the assignment Comes_From_Source,
767 -- because in some cases the expander generates such assignments (such
768 -- in the _assign operation for an abstract type).
770 elsif Is_Abstract_Type
(T1
) and then Comes_From_Source
(N
) then
772 ("target of assignment operation must not be abstract", Lhs
);
775 -- Variables which are Part_Of constituents of single protected types
776 -- behave in similar fashion to protected components. Such variables
777 -- cannot be modified by protected functions.
779 if Is_Protected_Part_Of_Constituent
(Lhs
) and then Within_Function
then
781 ("protected function cannot modify its protected object", Lhs
);
784 -- Resolution may have updated the subtype, in case the left-hand side
785 -- is a private protected component. Use the correct subtype to avoid
786 -- scoping issues in the back-end.
790 -- Ada 2005 (AI-50217, AI-326): Check wrong dereference of incomplete
791 -- type. For example:
795 -- type Acc is access P.T;
798 -- with Pkg; use Acc;
799 -- procedure Example is
802 -- A.all := B.all; -- ERROR
805 if Nkind
(Lhs
) = N_Explicit_Dereference
806 and then Ekind
(T1
) = E_Incomplete_Type
808 Error_Msg_N
("invalid use of incomplete type", Lhs
);
813 -- Now we can complete the resolution of the right hand side
815 Set_Assignment_Type
(Lhs
, T1
);
817 -- If the target of the assignment is an entity of a mutable type and
818 -- the expression is a conditional expression, its alternatives can be
819 -- of different subtypes of the nominal type of the LHS, so they must be
820 -- resolved with the base type, given that their subtype may differ from
821 -- that of the target mutable object.
823 if Is_Entity_Name
(Lhs
)
824 and then Is_Assignable
(Entity
(Lhs
))
825 and then Is_Composite_Type
(T1
)
826 and then not Is_Constrained
(Etype
(Entity
(Lhs
)))
827 and then Nkind
(Rhs
) in N_If_Expression | N_Case_Expression
829 Resolve
(Rhs
, Base_Type
(T1
));
835 -- This is the point at which we check for an unset reference
837 Check_Unset_Reference
(Rhs
);
838 Check_Unprotected_Access
(Lhs
, Rhs
);
840 -- Remaining steps are skipped if Rhs was syntactically in error
849 if not Covers
(T1
, T2
) then
850 Wrong_Type
(Rhs
, Etype
(Lhs
));
855 -- Ada 2005 (AI-326): In case of explicit dereference of incomplete
856 -- types, use the non-limited view if available
858 if Nkind
(Rhs
) = N_Explicit_Dereference
859 and then Is_Tagged_Type
(T2
)
860 and then Has_Non_Limited_View
(T2
)
862 T2
:= Non_Limited_View
(T2
);
865 Set_Assignment_Type
(Rhs
, T2
);
867 if Total_Errors_Detected
/= 0 then
877 if T1
= Any_Type
or else T2
= Any_Type
then
882 -- If the rhs is class-wide or dynamically tagged, then require the lhs
883 -- to be class-wide. The case where the rhs is a dynamically tagged call
884 -- to a dispatching operation with a controlling access result is
885 -- excluded from this check, since the target has an access type (and
886 -- no tag propagation occurs in that case).
888 if (Is_Class_Wide_Type
(T2
)
889 or else (Is_Dynamically_Tagged
(Rhs
)
890 and then not Is_Access_Type
(T1
)))
891 and then not Is_Class_Wide_Type
(T1
)
893 Error_Msg_N
("dynamically tagged expression not allowed!", Rhs
);
895 elsif Is_Class_Wide_Type
(T1
)
896 and then not Is_Class_Wide_Type
(T2
)
897 and then not Is_Tag_Indeterminate
(Rhs
)
898 and then not Is_Dynamically_Tagged
(Rhs
)
900 Error_Msg_N
("dynamically tagged expression required!", Rhs
);
903 -- Propagate the tag from a class-wide target to the rhs when the rhs
904 -- is a tag-indeterminate call.
906 if Is_Tag_Indeterminate
(Rhs
) then
907 if Is_Class_Wide_Type
(T1
) then
908 Propagate_Tag
(Lhs
, Rhs
);
910 elsif Nkind
(Rhs
) = N_Function_Call
911 and then Is_Entity_Name
(Name
(Rhs
))
912 and then Is_Abstract_Subprogram
(Entity
(Name
(Rhs
)))
915 ("call to abstract function must be dispatching", Name
(Rhs
));
917 elsif Nkind
(Rhs
) = N_Qualified_Expression
918 and then Nkind
(Expression
(Rhs
)) = N_Function_Call
919 and then Is_Entity_Name
(Name
(Expression
(Rhs
)))
921 Is_Abstract_Subprogram
(Entity
(Name
(Expression
(Rhs
))))
924 ("call to abstract function must be dispatching",
925 Name
(Expression
(Rhs
)));
929 -- Ada 2005 (AI-385): When the lhs type is an anonymous access type,
930 -- apply an implicit conversion of the rhs to that type to force
931 -- appropriate static and run-time accessibility checks. This applies
932 -- as well to anonymous access-to-subprogram types that are component
933 -- subtypes or formal parameters.
935 if Ada_Version
>= Ada_2005
and then Is_Access_Type
(T1
) then
936 if Is_Local_Anonymous_Access
(T1
)
937 or else Ekind
(T2
) = E_Anonymous_Access_Subprogram_Type
939 -- Handle assignment to an Ada 2012 stand-alone object
940 -- of an anonymous access type.
942 or else (Ekind
(T1
) = E_Anonymous_Access_Type
943 and then Nkind
(Associated_Node_For_Itype
(T1
)) =
944 N_Object_Declaration
)
947 Rewrite
(Rhs
, Convert_To
(T1
, Relocate_Node
(Rhs
)));
948 Analyze_And_Resolve
(Rhs
, T1
);
952 -- Ada 2005 (AI-231): Assignment to not null variable
954 if Ada_Version
>= Ada_2005
955 and then Can_Never_Be_Null
(T1
)
956 and then not Assignment_OK
(Lhs
)
958 -- Case where we know the right hand side is null
960 if Known_Null
(Rhs
) then
961 Apply_Compile_Time_Constraint_Error
964 "(Ada 2005) NULL not allowed in null-excluding objects??",
965 Reason
=> CE_Null_Not_Allowed
);
967 -- We still mark this as a possible modification, that's necessary
968 -- to reset Is_True_Constant, and desirable for xref purposes.
970 Note_Possible_Modification
(Lhs
, Sure
=> True);
973 -- If we know the right hand side is non-null, then we convert to the
974 -- target type, since we don't need a run time check in that case.
976 elsif not Can_Never_Be_Null
(T2
) then
977 Rewrite
(Rhs
, Convert_To
(T1
, Relocate_Node
(Rhs
)));
978 Analyze_And_Resolve
(Rhs
, T1
);
982 if Is_Scalar_Type
(T1
) then
985 function Omit_Range_Check_For_Streaming
return Boolean;
986 -- Return True if this assignment statement is the expansion of
987 -- a Some_Scalar_Type'Read procedure call such that all conditions
988 -- of 13.3.2(35)'s "no check is made" rule are met.
990 ------------------------------------
991 -- Omit_Range_Check_For_Streaming --
992 ------------------------------------
994 function Omit_Range_Check_For_Streaming
return Boolean is
996 -- Have we got an implicitly generated assignment to a
997 -- component of a composite object? If not, return False.
999 if Comes_From_Source
(N
)
1000 or else Serious_Errors_Detected
> 0
1002 not in N_Selected_Component | N_Indexed_Component
1008 Pref
: constant Node_Id
:= Prefix
(Lhs
);
1010 -- Are we in the implicitly-defined Read subprogram
1011 -- for a composite type, reading the value of a scalar
1012 -- component from the stream? If not, return False.
1014 if Nkind
(Pref
) /= N_Identifier
1015 or else not Is_TSS
(Scope
(Entity
(Pref
)), TSS_Stream_Read
)
1020 -- Return False if Default_Value or Default_Component_Value
1023 if Has_Default_Aspect
(Etype
(Lhs
))
1024 or else Has_Default_Aspect
(Etype
(Pref
))
1028 -- Are we assigning to a record component (as opposed to
1029 -- an array component)?
1031 elsif Nkind
(Lhs
) = N_Selected_Component
then
1033 -- Are we assigning to a nondiscriminant component
1034 -- that lacks a default initial value expression?
1035 -- If so, return True.
1038 Comp_Id
: constant Entity_Id
:=
1039 Original_Record_Component
1040 (Entity
(Selector_Name
(Lhs
)));
1042 if Ekind
(Comp_Id
) = E_Component
1043 and then Nkind
(Parent
(Comp_Id
))
1044 = N_Component_Declaration
1046 not Present
(Expression
(Parent
(Comp_Id
)))
1053 -- We are assigning to a component of an array
1054 -- (and we tested for both Default_Value and
1055 -- Default_Component_Value above), so return True.
1058 pragma Assert
(Nkind
(Lhs
) = N_Indexed_Component
);
1062 end Omit_Range_Check_For_Streaming
;
1065 if not Omit_Range_Check_For_Streaming
then
1066 Apply_Scalar_Range_Check
(Rhs
, Etype
(Lhs
));
1070 -- For array types, verify that lengths match. If the right hand side
1071 -- is a function call that has been inlined, the assignment has been
1072 -- rewritten as a block, and the constraint check will be applied to the
1073 -- assignment within the block.
1075 elsif Is_Array_Type
(T1
)
1076 and then (Nkind
(Rhs
) /= N_Type_Conversion
1077 or else Is_Constrained
(Etype
(Rhs
)))
1078 and then (Nkind
(Rhs
) /= N_Function_Call
1079 or else Nkind
(N
) /= N_Block_Statement
)
1081 -- Assignment verifies that the length of the Lhs and Rhs are equal,
1082 -- but of course the indexes do not have to match. If the right-hand
1083 -- side is a type conversion to an unconstrained type, a length check
1084 -- is performed on the expression itself during expansion. In rare
1085 -- cases, the redundant length check is computed on an index type
1086 -- with a different representation, triggering incorrect code in the
1089 Apply_Length_Check_On_Assignment
(Rhs
, Etype
(Lhs
), Lhs
);
1092 -- Discriminant checks are applied in the course of expansion
1097 -- Note: modifications of the Lhs may only be recorded after
1098 -- checks have been applied.
1100 Note_Possible_Modification
(Lhs
, Sure
=> True);
1102 -- ??? a real accessibility check is needed when ???
1104 -- Post warning for redundant assignment or variable to itself
1106 if Warn_On_Redundant_Constructs
1108 -- We only warn for source constructs
1110 and then Comes_From_Source
(N
)
1112 -- Where the object is the same on both sides
1114 and then Same_Object
(Lhs
, Original_Node
(Rhs
))
1116 -- But exclude the case where the right side was an operation that
1117 -- got rewritten (e.g. JUNK + K, where K was known to be zero). We
1118 -- don't want to warn in such a case, since it is reasonable to write
1119 -- such expressions especially when K is defined symbolically in some
1122 and then Nkind
(Original_Node
(Rhs
)) not in N_Op
1124 if Nkind
(Lhs
) in N_Has_Entity
then
1125 Error_Msg_NE
-- CODEFIX
1126 ("?r?useless assignment of & to itself!", N
, Entity
(Lhs
));
1128 Error_Msg_N
-- CODEFIX
1129 ("?r?useless assignment of object to itself!", N
);
1133 -- Check for non-allowed composite assignment
1135 if not Support_Composite_Assign_On_Target
1136 and then (Is_Array_Type
(T1
) or else Is_Record_Type
(T1
))
1137 and then (not Has_Size_Clause
(T1
)
1138 or else Esize
(T1
) > Ttypes
.System_Max_Integer_Size
)
1140 Error_Msg_CRT
("composite assignment", N
);
1143 -- Check elaboration warning for left side if not in elab code
1145 if Legacy_Elaboration_Checks
1146 and not In_Subprogram_Or_Concurrent_Unit
1148 Check_Elab_Assign
(Lhs
);
1151 -- Save the scenario for later examination by the ABE Processing phase
1153 Record_Elaboration_Scenario
(N
);
1155 -- Set Referenced_As_LHS if appropriate. We only set this flag if the
1156 -- assignment is a source assignment in the extended main source unit.
1157 -- We are not interested in any reference information outside this
1158 -- context, or in compiler generated assignment statements.
1160 if Comes_From_Source
(N
)
1161 and then In_Extended_Main_Source_Unit
(Lhs
)
1163 Set_Referenced_Modified
(Lhs
, Out_Param
=> False);
1166 -- RM 7.3.2 (12/3): An assignment to a view conversion (from a type to
1167 -- one of its ancestors) requires an invariant check. Apply check only
1168 -- if expression comes from source, otherwise it will be applied when
1169 -- value is assigned to source entity. This is not done in GNATprove
1170 -- mode, as GNATprove handles invariant checks itself.
1172 if Nkind
(Lhs
) = N_Type_Conversion
1173 and then Has_Invariants
(Etype
(Expression
(Lhs
)))
1174 and then Comes_From_Source
(Expression
(Lhs
))
1175 and then not GNATprove_Mode
1177 Insert_After
(N
, Make_Invariant_Call
(Expression
(Lhs
)));
1180 -- Final step. If left side is an entity, then we may be able to reset
1181 -- the current tracked values to new safe values. We only have something
1182 -- to do if the left side is an entity name, and expansion has not
1183 -- modified the node into something other than an assignment, and of
1184 -- course we only capture values if it is safe to do so.
1186 if Is_Entity_Name
(Lhs
)
1187 and then Nkind
(N
) = N_Assignment_Statement
1190 Ent
: constant Entity_Id
:= Entity
(Lhs
);
1193 if Safe_To_Capture_Value
(N
, Ent
) then
1195 -- If simple variable on left side, warn if this assignment
1196 -- blots out another one (rendering it useless). We only do
1197 -- this for source assignments, otherwise we can generate bogus
1198 -- warnings when an assignment is rewritten as another
1199 -- assignment, and gets tied up with itself.
1201 -- We also omit the warning if the RHS includes target names,
1202 -- that is to say the Ada 2022 "@" that denotes an instance of
1203 -- the LHS, which indicates that the current value is being
1204 -- used. Note that this implicit reference to the entity on
1205 -- the RHS is not treated as a source reference.
1207 -- There may have been a previous reference to a component of
1208 -- the variable, which in general removes the Last_Assignment
1209 -- field of the variable to indicate a relevant use of the
1210 -- previous assignment. However, if the assignment is to a
1211 -- subcomponent the reference may not have registered, because
1212 -- it is not possible to determine whether the context is an
1213 -- assignment. In those cases we generate a Deferred_Reference,
1214 -- to be used at the end of compilation to generate the right
1215 -- kind of reference, and we suppress a potential warning for
1216 -- a useless assignment, which might be premature. This may
1217 -- lose a warning in rare cases, but seems preferable to a
1218 -- misleading warning.
1220 if Warn_On_Modified_Unread
1221 and then Is_Assignable
(Ent
)
1222 and then Comes_From_Source
(N
)
1223 and then In_Extended_Main_Source_Unit
(Ent
)
1224 and then not Has_Deferred_Reference
(Ent
)
1225 and then not Has_Target_Names
(N
)
1227 Warn_On_Useless_Assignment
(Ent
, N
);
1230 -- If we are assigning an access type and the left side is an
1231 -- entity, then make sure that the Is_Known_[Non_]Null flags
1232 -- properly reflect the state of the entity after assignment.
1234 if Is_Access_Type
(T1
) then
1235 if Known_Non_Null
(Rhs
) then
1236 Set_Is_Known_Non_Null
(Ent
, True);
1238 elsif Known_Null
(Rhs
)
1239 and then not Can_Never_Be_Null
(Ent
)
1241 Set_Is_Known_Null
(Ent
, True);
1244 Set_Is_Known_Null
(Ent
, False);
1246 if not Can_Never_Be_Null
(Ent
) then
1247 Set_Is_Known_Non_Null
(Ent
, False);
1251 -- For discrete types, we may be able to set the current value
1252 -- if the value is known at compile time.
1254 elsif Is_Discrete_Type
(T1
)
1255 and then Compile_Time_Known_Value
(Rhs
)
1257 Set_Current_Value
(Ent
, Rhs
);
1259 Set_Current_Value
(Ent
, Empty
);
1262 -- If not safe to capture values, kill them
1270 -- If assigning to an object in whole or in part, note location of
1271 -- assignment in case no one references value. We only do this for
1272 -- source assignments, otherwise we can generate bogus warnings when an
1273 -- assignment is rewritten as another assignment, and gets tied up with
1277 Ent
: constant Entity_Id
:= Get_Enclosing_Object
(Lhs
);
1280 and then Safe_To_Capture_Value
(N
, Ent
)
1281 and then Nkind
(N
) = N_Assignment_Statement
1282 and then Warn_On_Modified_Unread
1283 and then Is_Assignable
(Ent
)
1284 and then Comes_From_Source
(N
)
1285 and then In_Extended_Main_Source_Unit
(Ent
)
1287 Set_Last_Assignment
(Ent
, Lhs
);
1291 Analyze_Dimension
(N
);
1294 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
1296 -- If the right-hand side contains target names, expansion has been
1297 -- disabled to prevent expansion that might move target names out of
1298 -- the context of the assignment statement. Restore the expander mode
1299 -- now so that assignment statement can be properly expanded.
1301 if Nkind
(N
) = N_Assignment_Statement
then
1302 if Has_Target_Names
(N
) then
1303 Expander_Mode_Restore
;
1304 Full_Analysis
:= Save_Full_Analysis
;
1305 Current_Assignment
:= Empty
;
1308 pragma Assert
(not Should_Transform_BIP_Assignment
(Typ
=> T1
));
1310 end Analyze_Assignment
;
1312 -----------------------------
1313 -- Analyze_Block_Statement --
1314 -----------------------------
1316 procedure Analyze_Block_Statement
(N
: Node_Id
) is
1317 procedure Install_Return_Entities
(Scop
: Entity_Id
);
1318 -- Install all entities of return statement scope Scop in the visibility
1319 -- chain except for the return object since its entity is reused in a
1322 -----------------------------
1323 -- Install_Return_Entities --
1324 -----------------------------
1326 procedure Install_Return_Entities
(Scop
: Entity_Id
) is
1330 Id
:= First_Entity
(Scop
);
1331 while Present
(Id
) loop
1333 -- Do not install the return object
1335 if Ekind
(Id
) not in E_Constant | E_Variable
1336 or else not Is_Return_Object
(Id
)
1338 Install_Entity
(Id
);
1343 end Install_Return_Entities
;
1345 -- Local constants and variables
1347 Decls
: constant List_Id
:= Declarations
(N
);
1348 Id
: constant Node_Id
:= Identifier
(N
);
1349 HSS
: constant Node_Id
:= Handled_Statement_Sequence
(N
);
1351 Is_BIP_Return_Statement
: Boolean;
1353 -- Start of processing for Analyze_Block_Statement
1356 -- If no handled statement sequence is present, things are really messed
1357 -- up, and we just return immediately (defence against previous errors).
1360 Check_Error_Detected
;
1364 -- Detect whether the block is actually a rewritten return statement of
1365 -- a build-in-place function.
1367 Is_BIP_Return_Statement
:=
1369 and then Present
(Entity
(Id
))
1370 and then Ekind
(Entity
(Id
)) = E_Return_Statement
1371 and then Is_Build_In_Place_Function
1372 (Return_Applies_To
(Entity
(Id
)));
1374 -- Normal processing with HSS present
1377 EH
: constant List_Id
:= Exception_Handlers
(HSS
);
1378 Ent
: Entity_Id
:= Empty
;
1381 Save_Unblocked_Exit_Count
: constant Nat
:= Unblocked_Exit_Count
;
1382 -- Recursively save value of this global, will be restored on exit
1385 -- Initialize unblocked exit count for statements of begin block
1386 -- plus one for each exception handler that is present.
1388 Unblocked_Exit_Count
:= 1;
1390 if Present
(EH
) then
1391 Unblocked_Exit_Count
:= Unblocked_Exit_Count
+ List_Length
(EH
);
1394 -- If a label is present analyze it and mark it as referenced
1396 if Present
(Id
) then
1400 -- An error defense. If we have an identifier, but no entity, then
1401 -- something is wrong. If previous errors, then just remove the
1402 -- identifier and continue, otherwise raise an exception.
1405 Check_Error_Detected
;
1406 Set_Identifier
(N
, Empty
);
1409 if Ekind
(Ent
) = E_Label
then
1410 Reinit_Field_To_Zero
(Ent
, F_Enclosing_Scope
);
1413 Mutate_Ekind
(Ent
, E_Block
);
1414 Generate_Reference
(Ent
, N
, ' ');
1415 Generate_Definition
(Ent
);
1417 if Nkind
(Parent
(Ent
)) = N_Implicit_Label_Declaration
then
1418 Set_Label_Construct
(Parent
(Ent
), N
);
1423 -- If no entity set, create a label entity
1426 Ent
:= New_Internal_Entity
(E_Block
, Current_Scope
, Sloc
(N
), 'B');
1427 Set_Identifier
(N
, New_Occurrence_Of
(Ent
, Sloc
(N
)));
1428 Set_Parent
(Ent
, N
);
1431 Set_Etype
(Ent
, Standard_Void_Type
);
1432 Set_Block_Node
(Ent
, Identifier
(N
));
1435 -- The block served as an extended return statement. Ensure that any
1436 -- entities created during the analysis and expansion of the return
1437 -- object declaration are once again visible.
1439 if Is_BIP_Return_Statement
then
1440 Install_Return_Entities
(Ent
);
1443 if Present
(Decls
) then
1444 Analyze_Declarations
(Decls
);
1446 Inspect_Deferred_Constant_Completion
(Decls
);
1450 Process_End_Label
(HSS
, 'e', Ent
);
1452 -- If exception handlers are present, then we indicate that enclosing
1453 -- scopes contain a block with handlers. We only need to mark non-
1456 if Present
(EH
) then
1459 Set_Has_Nested_Block_With_Handler
(S
);
1460 exit when Is_Overloadable
(S
)
1461 or else Ekind
(S
) = E_Package
1462 or else Is_Generic_Unit
(S
);
1467 Check_References
(Ent
);
1468 Update_Use_Clause_Chain
;
1471 if Unblocked_Exit_Count
= 0 then
1472 Unblocked_Exit_Count
:= Save_Unblocked_Exit_Count
;
1473 Check_Unreachable_Code
(N
);
1475 Unblocked_Exit_Count
:= Save_Unblocked_Exit_Count
;
1478 end Analyze_Block_Statement
;
1480 --------------------------------
1481 -- Analyze_Compound_Statement --
1482 --------------------------------
1484 procedure Analyze_Compound_Statement
(N
: Node_Id
) is
1486 Analyze_List
(Actions
(N
));
1487 end Analyze_Compound_Statement
;
1489 ----------------------------
1490 -- Analyze_Case_Statement --
1491 ----------------------------
1493 procedure Analyze_Case_Statement
(N
: Node_Id
) is
1494 Exp
: constant Node_Id
:= Expression
(N
);
1496 Statements_Analyzed
: Boolean := False;
1497 -- Set True if at least some statement sequences get analyzed. If False
1498 -- on exit, means we had a serious error that prevented full analysis of
1499 -- the case statement, and as a result it is not a good idea to output
1500 -- warning messages about unreachable code.
1502 Is_General_Case_Statement
: Boolean := False;
1503 -- Set True (later) if type of case expression is not discrete
1505 procedure Non_Static_Choice_Error
(Choice
: Node_Id
);
1506 -- Error routine invoked by the generic instantiation below when the
1507 -- case statement has a non static choice.
1509 procedure Process_Statements
(Alternative
: Node_Id
);
1510 -- Analyzes the statements associated with a case alternative. Needed
1511 -- by instantiation below.
1513 package Analyze_Case_Choices
is new
1514 Generic_Analyze_Choices
1515 (Process_Associated_Node
=> Process_Statements
);
1516 use Analyze_Case_Choices
;
1517 -- Instantiation of the generic choice analysis package
1519 package Check_Case_Choices
is new
1520 Generic_Check_Choices
1521 (Process_Empty_Choice
=> No_OP
,
1522 Process_Non_Static_Choice
=> Non_Static_Choice_Error
,
1523 Process_Associated_Node
=> No_OP
);
1524 use Check_Case_Choices
;
1525 -- Instantiation of the generic choice processing package
1527 -----------------------------
1528 -- Non_Static_Choice_Error --
1529 -----------------------------
1531 procedure Non_Static_Choice_Error
(Choice
: Node_Id
) is
1533 Flag_Non_Static_Expr
1534 ("choice given in case statement is not static!", Choice
);
1535 end Non_Static_Choice_Error
;
1537 ------------------------
1538 -- Process_Statements --
1539 ------------------------
1541 procedure Process_Statements
(Alternative
: Node_Id
) is
1542 Choices
: constant List_Id
:= Discrete_Choices
(Alternative
);
1546 if Is_General_Case_Statement
then
1548 -- Processing deferred in this case; decls associated with
1549 -- pattern match bindings don't exist yet.
1552 Unblocked_Exit_Count
:= Unblocked_Exit_Count
+ 1;
1553 Statements_Analyzed
:= True;
1555 -- An interesting optimization. If the case statement expression
1556 -- is a simple entity, then we can set the current value within an
1557 -- alternative if the alternative has one possible value.
1561 -- when 2 | 3 => beta
1562 -- when others => gamma
1564 -- Here we know that N is initially 1 within alpha, but for beta and
1565 -- gamma, we do not know anything more about the initial value.
1567 if Is_Entity_Name
(Exp
) then
1568 Ent
:= Entity
(Exp
);
1570 if Is_Object
(Ent
) then
1571 if List_Length
(Choices
) = 1
1572 and then Nkind
(First
(Choices
)) in N_Subexpr
1573 and then Compile_Time_Known_Value
(First
(Choices
))
1575 Set_Current_Value
(Entity
(Exp
), First
(Choices
));
1578 Analyze_Statements
(Statements
(Alternative
));
1580 -- After analyzing the case, set the current value to empty
1581 -- since we won't know what it is for the next alternative
1582 -- (unless reset by this same circuit), or after the case.
1584 Set_Current_Value
(Entity
(Exp
), Empty
);
1589 -- Case where expression is not an entity name of an object
1591 Analyze_Statements
(Statements
(Alternative
));
1592 end Process_Statements
;
1596 Exp_Type
: Entity_Id
;
1597 Exp_Btype
: Entity_Id
;
1599 Others_Present
: Boolean;
1600 -- Indicates if Others was present
1602 Save_Unblocked_Exit_Count
: constant Nat
:= Unblocked_Exit_Count
;
1603 -- Recursively save value of this global, will be restored on exit
1605 -- Start of processing for Analyze_Case_Statement
1610 -- The expression must be of any discrete type. In rare cases, the
1611 -- expander constructs a case statement whose expression has a private
1612 -- type whose full view is discrete. This can happen when generating
1613 -- a stream operation for a variant type after the type is frozen,
1614 -- when the partial of view of the type of the discriminant is private.
1615 -- In that case, use the full view to analyze case alternatives.
1617 if not Is_Overloaded
(Exp
)
1618 and then not Comes_From_Source
(N
)
1619 and then Is_Private_Type
(Etype
(Exp
))
1620 and then Present
(Full_View
(Etype
(Exp
)))
1621 and then Is_Discrete_Type
(Full_View
(Etype
(Exp
)))
1624 Exp_Type
:= Full_View
(Etype
(Exp
));
1626 -- For Ada, overloading might be ok because subsequently filtering
1627 -- out non-discretes may resolve the ambiguity.
1628 -- But GNAT extensions allow casing on non-discretes.
1630 elsif Extensions_Allowed
and then Is_Overloaded
(Exp
) then
1632 -- It would be nice if we could generate all the right error
1633 -- messages by calling "Resolve (Exp, Any_Type);" in the
1634 -- same way that they are generated a few lines below by the
1635 -- call "Analyze_And_Resolve (Exp, Any_Discrete);".
1636 -- Unfortunately, Any_Type and Any_Discrete are not treated
1637 -- consistently (specifically, by Sem_Type.Covers), so that
1641 ("selecting expression of general case statement is ambiguous",
1645 -- Check for a GNAT-extension "general" case statement (i.e., one where
1646 -- the type of the selecting expression is not discrete).
1648 elsif Extensions_Allowed
1649 and then not Is_Discrete_Type
(Etype
(Exp
))
1651 Resolve
(Exp
, Etype
(Exp
));
1652 Exp_Type
:= Etype
(Exp
);
1653 Is_General_Case_Statement
:= True;
1655 Analyze_And_Resolve
(Exp
, Any_Discrete
);
1656 Exp_Type
:= Etype
(Exp
);
1659 Check_Unset_Reference
(Exp
);
1660 Exp_Btype
:= Base_Type
(Exp_Type
);
1662 -- The expression must be of a discrete type which must be determinable
1663 -- independently of the context in which the expression occurs, but
1664 -- using the fact that the expression must be of a discrete type.
1665 -- Moreover, the type this expression must not be a character literal
1666 -- (which is always ambiguous) or, for Ada-83, a generic formal type.
1668 -- If error already reported by Resolve, nothing more to do
1670 if Exp_Btype
= Any_Discrete
or else Exp_Btype
= Any_Type
then
1673 elsif Exp_Btype
= Any_Character
then
1675 ("character literal as case expression is ambiguous", Exp
);
1678 elsif Ada_Version
= Ada_83
1679 and then (Is_Generic_Type
(Exp_Btype
)
1680 or else Is_Generic_Type
(Root_Type
(Exp_Btype
)))
1683 ("(Ada 83) case expression cannot be of a generic type", Exp
);
1686 elsif not Extensions_Allowed
1687 and then not Is_Discrete_Type
(Exp_Type
)
1690 ("expression in case statement must be of a discrete_Type", Exp
);
1694 -- If the case expression is a formal object of mode in out, then treat
1695 -- it as having a nonstatic subtype by forcing use of the base type
1696 -- (which has to get passed to Check_Case_Choices below). Also use base
1697 -- type when the case expression is parenthesized.
1699 if Paren_Count
(Exp
) > 0
1700 or else (Is_Entity_Name
(Exp
)
1701 and then Ekind
(Entity
(Exp
)) = E_Generic_In_Out_Parameter
)
1703 Exp_Type
:= Exp_Btype
;
1706 -- Call instantiated procedures to analyze and check discrete choices
1708 Unblocked_Exit_Count
:= 0;
1710 Analyze_Choices
(Alternatives
(N
), Exp_Type
);
1711 Check_Choices
(N
, Alternatives
(N
), Exp_Type
, Others_Present
);
1713 if Is_General_Case_Statement
then
1714 -- Work normally done in Process_Statements was deferred; do that
1715 -- deferred work now that Check_Choices has had a chance to create
1716 -- any needed pattern-match-binding declarations.
1718 Alt
: Node_Id
:= First
(Alternatives
(N
));
1720 while Present
(Alt
) loop
1721 Unblocked_Exit_Count
:= Unblocked_Exit_Count
+ 1;
1722 Analyze_Statements
(Statements
(Alt
));
1728 if Exp_Type
= Universal_Integer
and then not Others_Present
then
1729 Error_Msg_N
("case on universal integer requires OTHERS choice", Exp
);
1732 -- If all our exits were blocked by unconditional transfers of control,
1733 -- then the entire CASE statement acts as an unconditional transfer of
1734 -- control, so treat it like one, and check unreachable code. Skip this
1735 -- test if we had serious errors preventing any statement analysis.
1737 if Unblocked_Exit_Count
= 0 and then Statements_Analyzed
then
1738 Unblocked_Exit_Count
:= Save_Unblocked_Exit_Count
;
1739 Check_Unreachable_Code
(N
);
1741 Unblocked_Exit_Count
:= Save_Unblocked_Exit_Count
;
1744 -- If the expander is active it will detect the case of a statically
1745 -- determined single alternative and remove warnings for the case, but
1746 -- if we are not doing expansion, that circuit won't be active. Here we
1747 -- duplicate the effect of removing warnings in the same way, so that
1748 -- we will get the same set of warnings in -gnatc mode.
1750 if not Expander_Active
1751 and then Compile_Time_Known_Value
(Expression
(N
))
1752 and then Serious_Errors_Detected
= 0
1755 Chosen
: constant Node_Id
:= Find_Static_Alternative
(N
);
1759 Alt
:= First
(Alternatives
(N
));
1760 while Present
(Alt
) loop
1761 if Alt
/= Chosen
then
1762 Remove_Warning_Messages
(Statements
(Alt
));
1769 end Analyze_Case_Statement
;
1771 ----------------------------
1772 -- Analyze_Exit_Statement --
1773 ----------------------------
1775 -- If the exit includes a name, it must be the name of a currently open
1776 -- loop. Otherwise there must be an innermost open loop on the stack, to
1777 -- which the statement implicitly refers.
1779 -- Additionally, in SPARK mode:
1781 -- The exit can only name the closest enclosing loop;
1783 -- An exit with a when clause must be directly contained in a loop;
1785 -- An exit without a when clause must be directly contained in an
1786 -- if-statement with no elsif or else, which is itself directly contained
1787 -- in a loop. The exit must be the last statement in the if-statement.
1789 procedure Analyze_Exit_Statement
(N
: Node_Id
) is
1790 Target
: constant Node_Id
:= Name
(N
);
1791 Cond
: constant Node_Id
:= Condition
(N
);
1792 Scope_Id
: Entity_Id
:= Empty
; -- initialize to prevent warning
1798 Check_Unreachable_Code
(N
);
1801 if Present
(Target
) then
1803 U_Name
:= Entity
(Target
);
1805 if not In_Open_Scopes
(U_Name
) or else Ekind
(U_Name
) /= E_Loop
then
1806 Error_Msg_N
("invalid loop name in exit statement", N
);
1810 Set_Has_Exit
(U_Name
);
1817 for J
in reverse 0 .. Scope_Stack
.Last
loop
1818 Scope_Id
:= Scope_Stack
.Table
(J
).Entity
;
1819 Kind
:= Ekind
(Scope_Id
);
1821 if Kind
= E_Loop
and then (No
(Target
) or else Scope_Id
= U_Name
) then
1822 Set_Has_Exit
(Scope_Id
);
1825 elsif Kind
= E_Block
1826 or else Kind
= E_Loop
1827 or else Kind
= E_Return_Statement
1833 ("cannot exit from program unit or accept statement", N
);
1838 -- Verify that if present the condition is a Boolean expression
1840 if Present
(Cond
) then
1841 Analyze_And_Resolve
(Cond
, Any_Boolean
);
1842 Check_Unset_Reference
(Cond
);
1845 -- Chain exit statement to associated loop entity
1847 Set_Next_Exit_Statement
(N
, First_Exit_Statement
(Scope_Id
));
1848 Set_First_Exit_Statement
(Scope_Id
, N
);
1850 -- Since the exit may take us out of a loop, any previous assignment
1851 -- statement is not useless, so clear last assignment indications. It
1852 -- is OK to keep other current values, since if the exit statement
1853 -- does not exit, then the current values are still valid.
1855 Kill_Current_Values
(Last_Assignment_Only
=> True);
1856 end Analyze_Exit_Statement
;
1858 ----------------------------
1859 -- Analyze_Goto_Statement --
1860 ----------------------------
1862 procedure Analyze_Goto_Statement
(N
: Node_Id
) is
1863 Label
: constant Node_Id
:= Name
(N
);
1864 Scope_Id
: Entity_Id
;
1865 Label_Scope
: Entity_Id
;
1866 Label_Ent
: Entity_Id
;
1869 -- Actual semantic checks
1871 Check_Unreachable_Code
(N
);
1872 Kill_Current_Values
(Last_Assignment_Only
=> True);
1875 Label_Ent
:= Entity
(Label
);
1877 -- Ignore previous error
1879 if Label_Ent
= Any_Id
then
1880 Check_Error_Detected
;
1883 -- We just have a label as the target of a goto
1885 elsif Ekind
(Label_Ent
) /= E_Label
then
1886 Error_Msg_N
("target of goto statement must be a label", Label
);
1889 -- Check that the target of the goto is reachable according to Ada
1890 -- scoping rules. Note: the special gotos we generate for optimizing
1891 -- local handling of exceptions would violate these rules, but we mark
1892 -- such gotos as analyzed when built, so this code is never entered.
1894 elsif not Reachable
(Label_Ent
) then
1895 Error_Msg_N
("target of goto statement is not reachable", Label
);
1899 -- Here if goto passes initial validity checks
1901 Label_Scope
:= Enclosing_Scope
(Label_Ent
);
1903 for J
in reverse 0 .. Scope_Stack
.Last
loop
1904 Scope_Id
:= Scope_Stack
.Table
(J
).Entity
;
1906 if Label_Scope
= Scope_Id
1907 or else Ekind
(Scope_Id
) not in
1908 E_Block | E_Loop | E_Return_Statement
1910 if Scope_Id
/= Label_Scope
then
1912 ("cannot exit from program unit or accept statement", N
);
1919 raise Program_Error
;
1920 end Analyze_Goto_Statement
;
1922 ---------------------------------
1923 -- Analyze_Goto_When_Statement --
1924 ---------------------------------
1926 procedure Analyze_Goto_When_Statement
(N
: Node_Id
) is
1928 -- Verify the condition is a Boolean expression
1930 Analyze_And_Resolve
(Condition
(N
), Any_Boolean
);
1931 Check_Unset_Reference
(Condition
(N
));
1932 end Analyze_Goto_When_Statement
;
1934 --------------------------
1935 -- Analyze_If_Statement --
1936 --------------------------
1938 -- A special complication arises in the analysis of if statements
1940 -- The expander has circuitry to completely delete code that it can tell
1941 -- will not be executed (as a result of compile time known conditions). In
1942 -- the analyzer, we ensure that code that will be deleted in this manner
1943 -- is analyzed but not expanded. This is obviously more efficient, but
1944 -- more significantly, difficulties arise if code is expanded and then
1945 -- eliminated (e.g. exception table entries disappear). Similarly, itypes
1946 -- generated in deleted code must be frozen from start, because the nodes
1947 -- on which they depend will not be available at the freeze point.
1949 procedure Analyze_If_Statement
(N
: Node_Id
) is
1950 Save_Unblocked_Exit_Count
: constant Nat
:= Unblocked_Exit_Count
;
1951 -- Recursively save value of this global, will be restored on exit
1953 Save_In_Deleted_Code
: Boolean := In_Deleted_Code
;
1955 Del
: Boolean := False;
1956 -- This flag gets set True if a True condition has been found, which
1957 -- means that remaining ELSE/ELSIF parts are deleted.
1959 procedure Analyze_Cond_Then
(Cnode
: Node_Id
);
1960 -- This is applied to either the N_If_Statement node itself or to an
1961 -- N_Elsif_Part node. It deals with analyzing the condition and the THEN
1962 -- statements associated with it.
1964 -----------------------
1965 -- Analyze_Cond_Then --
1966 -----------------------
1968 procedure Analyze_Cond_Then
(Cnode
: Node_Id
) is
1969 Cond
: constant Node_Id
:= Condition
(Cnode
);
1970 Tstm
: constant List_Id
:= Then_Statements
(Cnode
);
1973 Unblocked_Exit_Count
:= Unblocked_Exit_Count
+ 1;
1974 Analyze_And_Resolve
(Cond
, Any_Boolean
);
1975 Check_Unset_Reference
(Cond
);
1976 Set_Current_Value_Condition
(Cnode
);
1978 -- If already deleting, then just analyze then statements
1981 Analyze_Statements
(Tstm
);
1983 -- Compile time known value, not deleting yet
1985 elsif Compile_Time_Known_Value
(Cond
) then
1986 Save_In_Deleted_Code
:= In_Deleted_Code
;
1988 -- If condition is True, then analyze the THEN statements and set
1989 -- no expansion for ELSE and ELSIF parts.
1991 if Is_True
(Expr_Value
(Cond
)) then
1992 Analyze_Statements
(Tstm
);
1994 Expander_Mode_Save_And_Set
(False);
1995 In_Deleted_Code
:= True;
1997 -- If condition is False, analyze THEN with expansion off
1999 else pragma Assert
(Is_False
(Expr_Value
(Cond
)));
2000 Expander_Mode_Save_And_Set
(False);
2001 In_Deleted_Code
:= True;
2002 Analyze_Statements
(Tstm
);
2003 Expander_Mode_Restore
;
2004 In_Deleted_Code
:= Save_In_Deleted_Code
;
2007 -- Not known at compile time, not deleting, normal analysis
2010 Analyze_Statements
(Tstm
);
2012 end Analyze_Cond_Then
;
2017 -- For iterating over elsif parts
2019 -- Start of processing for Analyze_If_Statement
2022 -- Initialize exit count for else statements. If there is no else part,
2023 -- this count will stay non-zero reflecting the fact that the uncovered
2024 -- else case is an unblocked exit.
2026 Unblocked_Exit_Count
:= 1;
2027 Analyze_Cond_Then
(N
);
2029 -- Now to analyze the elsif parts if any are present
2031 if Present
(Elsif_Parts
(N
)) then
2032 E
:= First
(Elsif_Parts
(N
));
2033 while Present
(E
) loop
2034 Analyze_Cond_Then
(E
);
2039 if Present
(Else_Statements
(N
)) then
2040 Analyze_Statements
(Else_Statements
(N
));
2043 -- If all our exits were blocked by unconditional transfers of control,
2044 -- then the entire IF statement acts as an unconditional transfer of
2045 -- control, so treat it like one, and check unreachable code.
2047 if Unblocked_Exit_Count
= 0 then
2048 Unblocked_Exit_Count
:= Save_Unblocked_Exit_Count
;
2049 Check_Unreachable_Code
(N
);
2051 Unblocked_Exit_Count
:= Save_Unblocked_Exit_Count
;
2055 Expander_Mode_Restore
;
2056 In_Deleted_Code
:= Save_In_Deleted_Code
;
2059 if not Expander_Active
2060 and then Compile_Time_Known_Value
(Condition
(N
))
2061 and then Serious_Errors_Detected
= 0
2063 if Is_True
(Expr_Value
(Condition
(N
))) then
2064 Remove_Warning_Messages
(Else_Statements
(N
));
2066 if Present
(Elsif_Parts
(N
)) then
2067 E
:= First
(Elsif_Parts
(N
));
2068 while Present
(E
) loop
2069 Remove_Warning_Messages
(Then_Statements
(E
));
2075 Remove_Warning_Messages
(Then_Statements
(N
));
2079 -- Warn on redundant if statement that has no effect
2081 -- Note, we could also check empty ELSIF parts ???
2083 if Warn_On_Redundant_Constructs
2085 -- If statement must be from source
2087 and then Comes_From_Source
(N
)
2089 -- Condition must not have obvious side effect
2091 and then Has_No_Obvious_Side_Effects
(Condition
(N
))
2093 -- No elsif parts of else part
2095 and then No
(Elsif_Parts
(N
))
2096 and then No
(Else_Statements
(N
))
2098 -- Then must be a single null statement
2100 and then List_Length
(Then_Statements
(N
)) = 1
2102 -- Go to original node, since we may have rewritten something as
2103 -- a null statement (e.g. a case we could figure the outcome of).
2106 T
: constant Node_Id
:= First
(Then_Statements
(N
));
2107 S
: constant Node_Id
:= Original_Node
(T
);
2110 if Comes_From_Source
(S
) and then Nkind
(S
) = N_Null_Statement
then
2111 Error_Msg_N
("if statement has no effect?r?", N
);
2115 end Analyze_If_Statement
;
2117 ----------------------------------------
2118 -- Analyze_Implicit_Label_Declaration --
2119 ----------------------------------------
2121 -- An implicit label declaration is generated in the innermost enclosing
2122 -- declarative part. This is done for labels, and block and loop names.
2124 -- Note: any changes in this routine may need to be reflected in
2125 -- Analyze_Label_Entity.
2127 procedure Analyze_Implicit_Label_Declaration
(N
: Node_Id
) is
2128 Id
: constant Node_Id
:= Defining_Identifier
(N
);
2131 Mutate_Ekind
(Id
, E_Label
);
2132 Set_Etype
(Id
, Standard_Void_Type
);
2133 Set_Enclosing_Scope
(Id
, Current_Scope
);
2134 end Analyze_Implicit_Label_Declaration
;
2136 ------------------------------
2137 -- Analyze_Iteration_Scheme --
2138 ------------------------------
2140 procedure Analyze_Iteration_Scheme
(N
: Node_Id
) is
2142 Iter_Spec
: Node_Id
;
2143 Loop_Spec
: Node_Id
;
2146 -- For an infinite loop, there is no iteration scheme
2152 Cond
:= Condition
(N
);
2153 Iter_Spec
:= Iterator_Specification
(N
);
2154 Loop_Spec
:= Loop_Parameter_Specification
(N
);
2156 if Present
(Cond
) then
2157 Analyze_And_Resolve
(Cond
, Any_Boolean
);
2158 Check_Unset_Reference
(Cond
);
2159 Set_Current_Value_Condition
(N
);
2161 elsif Present
(Iter_Spec
) then
2162 Analyze_Iterator_Specification
(Iter_Spec
);
2165 Analyze_Loop_Parameter_Specification
(Loop_Spec
);
2167 end Analyze_Iteration_Scheme
;
2169 ------------------------------------
2170 -- Analyze_Iterator_Specification --
2171 ------------------------------------
2173 procedure Analyze_Iterator_Specification
(N
: Node_Id
) is
2174 Def_Id
: constant Node_Id
:= Defining_Identifier
(N
);
2175 Iter_Name
: constant Node_Id
:= Name
(N
);
2176 Loc
: constant Source_Ptr
:= Sloc
(N
);
2177 Subt
: constant Node_Id
:= Subtype_Indication
(N
);
2179 Bas
: Entity_Id
:= Empty
; -- initialize to prevent warning
2182 procedure Check_Reverse_Iteration
(Typ
: Entity_Id
);
2183 -- For an iteration over a container, if the loop carries the Reverse
2184 -- indicator, verify that the container type has an Iterate aspect that
2185 -- implements the reversible iterator interface.
2187 procedure Check_Subtype_Definition
(Comp_Type
: Entity_Id
);
2188 -- If a subtype indication is present, verify that it is consistent
2189 -- with the component type of the array or container name.
2190 -- In Ada 2022, the subtype indication may be an access definition,
2191 -- if the array or container has elements of an anonymous access type.
2193 function Get_Cursor_Type
(Typ
: Entity_Id
) return Entity_Id
;
2194 -- For containers with Iterator and related aspects, the cursor is
2195 -- obtained by locating an entity with the proper name in the scope
2198 -----------------------------
2199 -- Check_Reverse_Iteration --
2200 -----------------------------
2202 procedure Check_Reverse_Iteration
(Typ
: Entity_Id
) is
2204 if Reverse_Present
(N
) then
2205 if Is_Array_Type
(Typ
)
2206 or else Is_Reversible_Iterator
(Typ
)
2208 (Present
(Find_Aspect
(Typ
, Aspect_Iterable
))
2211 (Get_Iterable_Type_Primitive
(Typ
, Name_Previous
)))
2216 ("container type does not support reverse iteration", N
);
2219 end Check_Reverse_Iteration
;
2221 -------------------------------
2222 -- Check_Subtype_Definition --
2223 -------------------------------
2225 procedure Check_Subtype_Definition
(Comp_Type
: Entity_Id
) is
2227 if not Present
(Subt
) then
2231 if Is_Anonymous_Access_Type
(Entity
(Subt
)) then
2232 if not Is_Anonymous_Access_Type
(Comp_Type
) then
2234 ("component type& is not an anonymous access",
2237 elsif not Conforming_Types
2238 (Designated_Type
(Entity
(Subt
)),
2239 Designated_Type
(Comp_Type
),
2243 ("subtype indication does not match component type&",
2247 elsif Present
(Subt
)
2248 and then (not Covers
(Base_Type
(Bas
), Comp_Type
)
2249 or else not Subtypes_Statically_Match
(Bas
, Comp_Type
))
2251 if Is_Array_Type
(Typ
) then
2253 ("subtype indication does not match component type&",
2257 ("subtype indication does not match element type&",
2261 end Check_Subtype_Definition
;
2263 ---------------------
2264 -- Get_Cursor_Type --
2265 ---------------------
2267 function Get_Cursor_Type
(Typ
: Entity_Id
) return Entity_Id
is
2271 -- If iterator type is derived, the cursor is declared in the scope
2272 -- of the parent type.
2274 if Is_Derived_Type
(Typ
) then
2275 Ent
:= First_Entity
(Scope
(Etype
(Typ
)));
2277 Ent
:= First_Entity
(Scope
(Typ
));
2280 while Present
(Ent
) loop
2281 exit when Chars
(Ent
) = Name_Cursor
;
2289 -- The cursor is the target of generated assignments in the
2290 -- loop, and cannot have a limited type.
2292 if Is_Limited_Type
(Etype
(Ent
)) then
2293 Error_Msg_N
("cursor type cannot be limited", N
);
2297 end Get_Cursor_Type
;
2299 -- Start of processing for Analyze_Iterator_Specification
2302 Enter_Name
(Def_Id
);
2304 -- AI12-0151 specifies that when the subtype indication is present, it
2305 -- must statically match the type of the array or container element.
2306 -- To simplify this check, we introduce a subtype declaration with the
2307 -- given subtype indication when it carries a constraint, and rewrite
2308 -- the original as a reference to the created subtype entity.
2310 if Present
(Subt
) then
2311 if Nkind
(Subt
) = N_Subtype_Indication
then
2313 S
: constant Entity_Id
:= Make_Temporary
(Sloc
(Subt
), 'S');
2314 Decl
: constant Node_Id
:=
2315 Make_Subtype_Declaration
(Loc
,
2316 Defining_Identifier
=> S
,
2317 Subtype_Indication
=> New_Copy_Tree
(Subt
));
2319 Insert_Before
(Parent
(Parent
(N
)), Decl
);
2321 Rewrite
(Subt
, New_Occurrence_Of
(S
, Sloc
(Subt
)));
2324 -- Ada 2022: the subtype definition may be for an anonymous
2327 elsif Nkind
(Subt
) = N_Access_Definition
then
2329 S
: constant Entity_Id
:= Make_Temporary
(Sloc
(Subt
), 'S');
2332 if Present
(Subtype_Mark
(Subt
)) then
2334 Make_Full_Type_Declaration
(Loc
,
2335 Defining_Identifier
=> S
,
2337 Make_Access_To_Object_Definition
(Loc
,
2338 All_Present
=> True,
2339 Subtype_Indication
=>
2340 New_Copy_Tree
(Subtype_Mark
(Subt
))));
2344 Make_Full_Type_Declaration
(Loc
,
2345 Defining_Identifier
=> S
,
2348 (Access_To_Subprogram_Definition
(Subt
)));
2351 Insert_Before
(Parent
(Parent
(N
)), Decl
);
2353 Freeze_Before
(First
(Statements
(Parent
(Parent
(N
)))), S
);
2354 Rewrite
(Subt
, New_Occurrence_Of
(S
, Sloc
(Subt
)));
2360 -- Save entity of subtype indication for subsequent check
2362 Bas
:= Entity
(Subt
);
2365 Preanalyze_Range
(Iter_Name
);
2367 -- If the domain of iteration is a function call, make sure the function
2368 -- itself is frozen. This is an issue if this is a local expression
2371 if Nkind
(Iter_Name
) = N_Function_Call
2372 and then Is_Entity_Name
(Name
(Iter_Name
))
2373 and then Full_Analysis
2374 and then (In_Assertion_Expr
= 0 or else Assertions_Enabled
)
2376 Freeze_Before
(N
, Entity
(Name
(Iter_Name
)));
2379 -- Set the kind of the loop variable, which is not visible within the
2382 Mutate_Ekind
(Def_Id
, E_Variable
);
2384 -- Provide a link between the iterator variable and the container, for
2385 -- subsequent use in cross-reference and modification information.
2387 if Of_Present
(N
) then
2388 Set_Related_Expression
(Def_Id
, Iter_Name
);
2390 -- For a container, the iterator is specified through the aspect
2392 if not Is_Array_Type
(Etype
(Iter_Name
)) then
2394 Iterator
: constant Entity_Id
:=
2395 Find_Value_Of_Aspect
2396 (Etype
(Iter_Name
), Aspect_Default_Iterator
);
2402 -- The domain of iteration must implement either the RM
2403 -- iterator interface, or the SPARK Iterable aspect.
2405 if No
(Iterator
) then
2406 if No
(Find_Aspect
(Etype
(Iter_Name
), Aspect_Iterable
)) then
2408 ("cannot iterate over&",
2409 N
, Base_Type
(Etype
(Iter_Name
)));
2413 elsif not Is_Overloaded
(Iterator
) then
2414 Check_Reverse_Iteration
(Etype
(Iterator
));
2416 -- If Iterator is overloaded, use reversible iterator if one is
2419 elsif Is_Overloaded
(Iterator
) then
2420 Get_First_Interp
(Iterator
, I
, It
);
2421 while Present
(It
.Nam
) loop
2422 if Ekind
(It
.Nam
) = E_Function
2423 and then Is_Reversible_Iterator
(Etype
(It
.Nam
))
2425 Set_Etype
(Iterator
, It
.Typ
);
2426 Set_Entity
(Iterator
, It
.Nam
);
2430 Get_Next_Interp
(I
, It
);
2433 Check_Reverse_Iteration
(Etype
(Iterator
));
2439 -- If the domain of iteration is an expression, create a declaration for
2440 -- it, so that finalization actions are introduced outside of the loop.
2441 -- The declaration must be a renaming (both in GNAT and GNATprove
2442 -- modes), because the body of the loop may assign to elements.
2444 if not Is_Entity_Name
(Iter_Name
)
2446 -- When the context is a quantified expression, the renaming
2447 -- declaration is delayed until the expansion phase if we are
2450 and then (Nkind
(Parent
(N
)) /= N_Quantified_Expression
2451 or else (Operating_Mode
= Check_Semantics
2452 and then not GNATprove_Mode
))
2454 -- Do not perform this expansion when expansion is disabled, where the
2455 -- temporary may hide the transformation of a selected component into
2456 -- a prefixed function call, and references need to see the original
2459 and then (Expander_Active
or GNATprove_Mode
)
2462 Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'R', Iter_Name
);
2468 -- If the domain of iteration is an array component that depends
2469 -- on a discriminant, create actual subtype for it. Preanalysis
2470 -- does not generate the actual subtype of a selected component.
2472 if Nkind
(Iter_Name
) = N_Selected_Component
2473 and then Is_Array_Type
(Etype
(Iter_Name
))
2476 Build_Actual_Subtype_Of_Component
2477 (Etype
(Selector_Name
(Iter_Name
)), Iter_Name
);
2478 Insert_Action
(N
, Act_S
);
2480 if Present
(Act_S
) then
2481 Typ
:= Defining_Identifier
(Act_S
);
2483 Typ
:= Etype
(Iter_Name
);
2487 Typ
:= Etype
(Iter_Name
);
2489 -- Verify that the expression produces an iterator
2491 if not Of_Present
(N
) and then not Is_Iterator
(Typ
)
2492 and then not Is_Array_Type
(Typ
)
2493 and then No
(Find_Aspect
(Typ
, Aspect_Iterable
))
2496 ("expect object that implements iterator interface",
2501 -- Protect against malformed iterator
2503 if Typ
= Any_Type
then
2504 Error_Msg_N
("invalid expression in loop iterator", Iter_Name
);
2508 if not Of_Present
(N
) then
2509 Check_Reverse_Iteration
(Typ
);
2512 -- For an element iteration over a slice, we must complete
2513 -- the resolution and expansion of the slice bounds. These
2514 -- can be arbitrary expressions, and the preanalysis that
2515 -- was performed in preparation for the iteration may have
2516 -- generated an itype whose bounds must be fully expanded.
2517 -- We set the parent node to provide a proper insertion
2518 -- point for generated actions, if any.
2520 if Nkind
(Iter_Name
) = N_Slice
2521 and then Nkind
(Discrete_Range
(Iter_Name
)) = N_Range
2522 and then not Analyzed
(Discrete_Range
(Iter_Name
))
2525 Indx
: constant Node_Id
:=
2526 Entity
(First_Index
(Etype
(Iter_Name
)));
2528 Set_Parent
(Indx
, Iter_Name
);
2529 Resolve
(Scalar_Range
(Indx
), Etype
(Indx
));
2533 -- The name in the renaming declaration may be a function call.
2534 -- Indicate that it does not come from source, to suppress
2535 -- spurious warnings on renamings of parameterless functions,
2536 -- a common enough idiom in user-defined iterators.
2539 Make_Object_Renaming_Declaration
(Loc
,
2540 Defining_Identifier
=> Id
,
2541 Subtype_Mark
=> New_Occurrence_Of
(Typ
, Loc
),
2543 New_Copy_Tree
(Iter_Name
, New_Sloc
=> Loc
));
2545 Insert_Actions
(Parent
(Parent
(N
)), New_List
(Decl
));
2546 Rewrite
(Name
(N
), New_Occurrence_Of
(Id
, Loc
));
2548 Set_Etype
(Id
, Typ
);
2549 Set_Etype
(Name
(N
), Typ
);
2552 -- Container is an entity or an array with uncontrolled components, or
2553 -- else it is a container iterator given by a function call, typically
2554 -- called Iterate in the case of predefined containers, even though
2555 -- Iterate is not a reserved name. What matters is that the return type
2556 -- of the function is an iterator type.
2558 elsif Is_Entity_Name
(Iter_Name
) then
2559 Analyze
(Iter_Name
);
2561 if Nkind
(Iter_Name
) = N_Function_Call
then
2563 C
: constant Node_Id
:= Name
(Iter_Name
);
2568 if not Is_Overloaded
(Iter_Name
) then
2569 Resolve
(Iter_Name
, Etype
(C
));
2572 Get_First_Interp
(C
, I
, It
);
2573 while It
.Typ
/= Empty
loop
2574 if Reverse_Present
(N
) then
2575 if Is_Reversible_Iterator
(It
.Typ
) then
2576 Resolve
(Iter_Name
, It
.Typ
);
2580 elsif Is_Iterator
(It
.Typ
) then
2581 Resolve
(Iter_Name
, It
.Typ
);
2585 Get_Next_Interp
(I
, It
);
2590 -- Domain of iteration is not overloaded
2593 Resolve
(Iter_Name
);
2596 if not Of_Present
(N
) then
2597 Check_Reverse_Iteration
(Etype
(Iter_Name
));
2601 -- Get base type of container, for proper retrieval of Cursor type
2602 -- and primitive operations.
2604 Typ
:= Base_Type
(Etype
(Iter_Name
));
2606 if Is_Array_Type
(Typ
) then
2607 if Of_Present
(N
) then
2608 Set_Etype
(Def_Id
, Component_Type
(Typ
));
2610 -- The loop variable is aliased if the array components are
2611 -- aliased. Likewise for the independent aspect.
2613 Set_Is_Aliased
(Def_Id
, Has_Aliased_Components
(Typ
));
2614 Set_Is_Independent
(Def_Id
, Has_Independent_Components
(Typ
));
2616 -- AI12-0047 stipulates that the domain (array or container)
2617 -- cannot be a component that depends on a discriminant if the
2618 -- enclosing object is mutable, to prevent a modification of the
2619 -- domain of iteration in the course of an iteration.
2621 -- If the object is an expression it has been captured in a
2622 -- temporary, so examine original node.
2624 if Nkind
(Original_Node
(Iter_Name
)) = N_Selected_Component
2625 and then Is_Dependent_Component_Of_Mutable_Object
2626 (Original_Node
(Iter_Name
))
2629 ("iterable name cannot be a discriminant-dependent "
2630 & "component of a mutable object", N
);
2633 Check_Subtype_Definition
(Component_Type
(Typ
));
2635 -- Here we have a missing Range attribute
2639 ("missing Range attribute in iteration over an array", N
);
2641 -- In Ada 2012 mode, this may be an attempt at an iterator
2643 if Ada_Version
>= Ada_2012
then
2645 ("\if& is meant to designate an element of the array, use OF",
2649 -- Prevent cascaded errors
2651 Mutate_Ekind
(Def_Id
, E_Loop_Parameter
);
2652 Set_Etype
(Def_Id
, Etype
(First_Index
(Typ
)));
2655 -- Check for type error in iterator
2657 elsif Typ
= Any_Type
then
2660 -- Iteration over a container
2663 Mutate_Ekind
(Def_Id
, E_Loop_Parameter
);
2664 Error_Msg_Ada_2012_Feature
("container iterator", Sloc
(N
));
2668 if Of_Present
(N
) then
2669 if Has_Aspect
(Typ
, Aspect_Iterable
) then
2671 Elt
: constant Entity_Id
:=
2672 Get_Iterable_Type_Primitive
(Typ
, Name_Element
);
2676 ("missing Element primitive for iteration", N
);
2678 Set_Etype
(Def_Id
, Etype
(Elt
));
2679 Check_Reverse_Iteration
(Typ
);
2683 Check_Subtype_Definition
(Etype
(Def_Id
));
2685 -- For a predefined container, the type of the loop variable is
2686 -- the Iterator_Element aspect of the container type.
2690 Element
: constant Entity_Id
:=
2691 Find_Value_Of_Aspect
2692 (Typ
, Aspect_Iterator_Element
);
2693 Iterator
: constant Entity_Id
:=
2694 Find_Value_Of_Aspect
2695 (Typ
, Aspect_Default_Iterator
);
2696 Orig_Iter_Name
: constant Node_Id
:=
2697 Original_Node
(Iter_Name
);
2698 Cursor_Type
: Entity_Id
;
2701 if No
(Element
) then
2702 Error_Msg_NE
("cannot iterate over&", N
, Typ
);
2706 Set_Etype
(Def_Id
, Entity
(Element
));
2707 Cursor_Type
:= Get_Cursor_Type
(Typ
);
2708 pragma Assert
(Present
(Cursor_Type
));
2710 Check_Subtype_Definition
(Etype
(Def_Id
));
2712 -- If the container has a variable indexing aspect, the
2713 -- element is a variable and is modifiable in the loop.
2715 if Has_Aspect
(Typ
, Aspect_Variable_Indexing
) then
2716 Mutate_Ekind
(Def_Id
, E_Variable
);
2719 -- If the container is a constant, iterating over it
2720 -- requires a Constant_Indexing operation.
2722 if not Is_Variable
(Iter_Name
)
2723 and then not Has_Aspect
(Typ
, Aspect_Constant_Indexing
)
2726 ("iteration over constant container require "
2727 & "constant_indexing aspect", N
);
2729 -- The Iterate function may have an in_out parameter,
2730 -- and a constant container is thus illegal.
2732 elsif Present
(Iterator
)
2733 and then Ekind
(Entity
(Iterator
)) = E_Function
2734 and then Ekind
(First_Formal
(Entity
(Iterator
))) /=
2736 and then not Is_Variable
(Iter_Name
)
2738 Error_Msg_N
("variable container expected", N
);
2741 -- Detect a case where the iterator denotes a component
2742 -- of a mutable object which depends on a discriminant.
2743 -- Note that the iterator may denote a function call in
2744 -- qualified form, in which case this check should not
2747 if Nkind
(Orig_Iter_Name
) = N_Selected_Component
2749 Present
(Entity
(Selector_Name
(Orig_Iter_Name
)))
2751 Ekind
(Entity
(Selector_Name
(Orig_Iter_Name
))) in
2752 E_Component | E_Discriminant
2753 and then Is_Dependent_Component_Of_Mutable_Object
2757 ("container cannot be a discriminant-dependent "
2758 & "component of a mutable object", N
);
2764 -- IN iterator, domain is a range, or a call to Iterate function
2767 -- For an iteration of the form IN, the name must denote an
2768 -- iterator, typically the result of a call to Iterate. Give a
2769 -- useful error message when the name is a container by itself.
2771 -- The type may be a formal container type, which has to have
2772 -- an Iterable aspect detailing the required primitives.
2774 if Is_Entity_Name
(Original_Node
(Name
(N
)))
2775 and then not Is_Iterator
(Typ
)
2777 if Has_Aspect
(Typ
, Aspect_Iterable
) then
2780 elsif not Has_Aspect
(Typ
, Aspect_Iterator_Element
) then
2782 ("cannot iterate over&", Name
(N
), Typ
);
2785 ("name must be an iterator, not a container", Name
(N
));
2788 if Has_Aspect
(Typ
, Aspect_Iterable
) then
2792 ("\to iterate directly over the elements of a container, "
2793 & "write `of &`", Name
(N
), Original_Node
(Name
(N
)));
2795 -- No point in continuing analysis of iterator spec
2801 -- If the name is a call (typically prefixed) to some Iterate
2802 -- function, it has been rewritten as an object declaration.
2803 -- If that object is a selected component, verify that it is not
2804 -- a component of an unconstrained mutable object.
2806 if Nkind
(Iter_Name
) = N_Identifier
2807 or else (not Expander_Active
and Comes_From_Source
(Iter_Name
))
2810 Orig_Node
: constant Node_Id
:= Original_Node
(Iter_Name
);
2811 Iter_Kind
: constant Node_Kind
:= Nkind
(Orig_Node
);
2815 if Iter_Kind
= N_Selected_Component
then
2816 Obj
:= Prefix
(Orig_Node
);
2818 elsif Iter_Kind
= N_Function_Call
then
2819 Obj
:= First_Actual
(Orig_Node
);
2821 -- If neither, the name comes from source
2827 if Nkind
(Obj
) = N_Selected_Component
2828 and then Is_Dependent_Component_Of_Mutable_Object
(Obj
)
2831 ("container cannot be a discriminant-dependent "
2832 & "component of a mutable object", N
);
2837 -- The result type of Iterate function is the classwide type of
2838 -- the interface parent. We need the specific Cursor type defined
2839 -- in the container package. We obtain it by name for a predefined
2840 -- container, or through the Iterable aspect for a formal one.
2842 if Has_Aspect
(Typ
, Aspect_Iterable
) then
2845 (Parent
(Find_Value_Of_Aspect
(Typ
, Aspect_Iterable
)),
2849 Set_Etype
(Def_Id
, Get_Cursor_Type
(Typ
));
2850 Check_Reverse_Iteration
(Etype
(Iter_Name
));
2856 if Present
(Iterator_Filter
(N
)) then
2857 -- Preanalyze the filter. Expansion will take place when enclosing
2858 -- loop is expanded.
2860 Preanalyze_And_Resolve
(Iterator_Filter
(N
), Standard_Boolean
);
2862 end Analyze_Iterator_Specification
;
2868 -- Note: the semantic work required for analyzing labels (setting them as
2869 -- reachable) was done in a prepass through the statements in the block,
2870 -- so that forward gotos would be properly handled. See Analyze_Statements
2871 -- for further details. The only processing required here is to deal with
2872 -- optimizations that depend on an assumption of sequential control flow,
2873 -- since of course the occurrence of a label breaks this assumption.
2875 procedure Analyze_Label
(N
: Node_Id
) is
2876 pragma Warnings
(Off
, N
);
2878 Kill_Current_Values
;
2881 --------------------------
2882 -- Analyze_Label_Entity --
2883 --------------------------
2885 procedure Analyze_Label_Entity
(E
: Entity_Id
) is
2887 Mutate_Ekind
(E
, E_Label
);
2888 Set_Etype
(E
, Standard_Void_Type
);
2889 Set_Enclosing_Scope
(E
, Current_Scope
);
2890 Set_Reachable
(E
, True);
2891 end Analyze_Label_Entity
;
2893 ------------------------------------------
2894 -- Analyze_Loop_Parameter_Specification --
2895 ------------------------------------------
2897 procedure Analyze_Loop_Parameter_Specification
(N
: Node_Id
) is
2898 Loop_Nod
: constant Node_Id
:= Parent
(Parent
(N
));
2900 procedure Check_Controlled_Array_Attribute
(DS
: Node_Id
);
2901 -- If the bounds are given by a 'Range reference on a function call
2902 -- that returns a controlled array, introduce an explicit declaration
2903 -- to capture the bounds, so that the function result can be finalized
2904 -- in timely fashion.
2906 procedure Check_Predicate_Use
(T
: Entity_Id
);
2907 -- Diagnose Attempt to iterate through non-static predicate. Note that
2908 -- a type with inherited predicates may have both static and dynamic
2909 -- forms. In this case it is not sufficent to check the static predicate
2910 -- function only, look for a dynamic predicate aspect as well.
2912 procedure Process_Bounds
(R
: Node_Id
);
2913 -- If the iteration is given by a range, create temporaries and
2914 -- assignment statements block to capture the bounds and perform
2915 -- required finalization actions in case a bound includes a function
2916 -- call that uses the temporary stack. We first preanalyze a copy of
2917 -- the range in order to determine the expected type, and analyze and
2918 -- resolve the original bounds.
2920 --------------------------------------
2921 -- Check_Controlled_Array_Attribute --
2922 --------------------------------------
2924 procedure Check_Controlled_Array_Attribute
(DS
: Node_Id
) is
2926 if Nkind
(DS
) = N_Attribute_Reference
2927 and then Is_Entity_Name
(Prefix
(DS
))
2928 and then Ekind
(Entity
(Prefix
(DS
))) = E_Function
2929 and then Is_Array_Type
(Etype
(Entity
(Prefix
(DS
))))
2931 Is_Controlled
(Component_Type
(Etype
(Entity
(Prefix
(DS
)))))
2932 and then Expander_Active
2935 Loc
: constant Source_Ptr
:= Sloc
(N
);
2936 Arr
: constant Entity_Id
:= Etype
(Entity
(Prefix
(DS
)));
2937 Indx
: constant Entity_Id
:=
2938 Base_Type
(Etype
(First_Index
(Arr
)));
2939 Subt
: constant Entity_Id
:= Make_Temporary
(Loc
, 'S');
2944 Make_Subtype_Declaration
(Loc
,
2945 Defining_Identifier
=> Subt
,
2946 Subtype_Indication
=>
2947 Make_Subtype_Indication
(Loc
,
2948 Subtype_Mark
=> New_Occurrence_Of
(Indx
, Loc
),
2950 Make_Range_Constraint
(Loc
, Relocate_Node
(DS
))));
2951 Insert_Before
(Loop_Nod
, Decl
);
2955 Make_Attribute_Reference
(Loc
,
2956 Prefix
=> New_Occurrence_Of
(Subt
, Loc
),
2957 Attribute_Name
=> Attribute_Name
(DS
)));
2962 end Check_Controlled_Array_Attribute
;
2964 -------------------------
2965 -- Check_Predicate_Use --
2966 -------------------------
2968 procedure Check_Predicate_Use
(T
: Entity_Id
) is
2970 -- A predicated subtype is illegal in loops and related constructs
2971 -- if the predicate is not static, or if it is a non-static subtype
2972 -- of a statically predicated subtype.
2974 if Is_Discrete_Type
(T
)
2975 and then Has_Predicates
(T
)
2976 and then (not Has_Static_Predicate
(T
)
2977 or else not Is_Static_Subtype
(T
)
2978 or else Has_Dynamic_Predicate_Aspect
(T
))
2980 -- Seems a confusing message for the case of a static predicate
2981 -- with a non-static subtype???
2983 Bad_Predicated_Subtype_Use
2984 ("cannot use subtype& with non-static predicate for loop "
2985 & "iteration", Discrete_Subtype_Definition
(N
),
2986 T
, Suggest_Static
=> True);
2988 elsif Inside_A_Generic
2989 and then Is_Generic_Formal
(T
)
2990 and then Is_Discrete_Type
(T
)
2992 Set_No_Dynamic_Predicate_On_Actual
(T
);
2994 end Check_Predicate_Use
;
2996 --------------------
2997 -- Process_Bounds --
2998 --------------------
3000 procedure Process_Bounds
(R
: Node_Id
) is
3001 Loc
: constant Source_Ptr
:= Sloc
(N
);
3004 (Original_Bound
: Node_Id
;
3005 Analyzed_Bound
: Node_Id
;
3006 Typ
: Entity_Id
) return Node_Id
;
3007 -- Capture value of bound and return captured value
3014 (Original_Bound
: Node_Id
;
3015 Analyzed_Bound
: Node_Id
;
3016 Typ
: Entity_Id
) return Node_Id
3023 -- If the bound is a constant or an object, no need for a separate
3024 -- declaration. If the bound is the result of previous expansion
3025 -- it is already analyzed and should not be modified. Note that
3026 -- the Bound will be resolved later, if needed, as part of the
3027 -- call to Make_Index (literal bounds may need to be resolved to
3030 if Analyzed
(Original_Bound
) then
3031 return Original_Bound
;
3033 elsif Nkind
(Analyzed_Bound
) in
3034 N_Integer_Literal | N_Character_Literal
3035 or else Is_Entity_Name
(Analyzed_Bound
)
3037 Analyze_And_Resolve
(Original_Bound
, Typ
);
3038 return Original_Bound
;
3040 elsif Inside_Class_Condition_Preanalysis
then
3041 Analyze_And_Resolve
(Original_Bound
, Typ
);
3042 return Original_Bound
;
3045 -- Normally, the best approach is simply to generate a constant
3046 -- declaration that captures the bound. However, there is a nasty
3047 -- case where this is wrong. If the bound is complex, and has a
3048 -- possible use of the secondary stack, we need to generate a
3049 -- separate assignment statement to ensure the creation of a block
3050 -- which will release the secondary stack.
3052 -- We prefer the constant declaration, since it leaves us with a
3053 -- proper trace of the value, useful in optimizations that get rid
3054 -- of junk range checks.
3056 if not Has_Sec_Stack_Call
(Analyzed_Bound
) then
3057 Analyze_And_Resolve
(Original_Bound
, Typ
);
3059 -- Ensure that the bound is valid. This check should not be
3060 -- generated when the range belongs to a quantified expression
3061 -- as the construct is still not expanded into its final form.
3063 if Nkind
(Parent
(R
)) /= N_Loop_Parameter_Specification
3064 or else Nkind
(Parent
(Parent
(R
))) /= N_Quantified_Expression
3066 Ensure_Valid
(Original_Bound
);
3069 Force_Evaluation
(Original_Bound
);
3070 return Original_Bound
;
3073 Id
:= Make_Temporary
(Loc
, 'R', Original_Bound
);
3075 -- Here we make a declaration with a separate assignment
3076 -- statement, and insert before loop header.
3079 Make_Object_Declaration
(Loc
,
3080 Defining_Identifier
=> Id
,
3081 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
3084 Make_Assignment_Statement
(Loc
,
3085 Name
=> New_Occurrence_Of
(Id
, Loc
),
3086 Expression
=> Relocate_Node
(Original_Bound
));
3088 Insert_Actions
(Loop_Nod
, New_List
(Decl
, Assign
));
3090 -- Now that this temporary variable is initialized we decorate it
3091 -- as safe-to-reevaluate to inform to the backend that no further
3092 -- asignment will be issued and hence it can be handled as side
3093 -- effect free. Note that this decoration must be done when the
3094 -- assignment has been analyzed because otherwise it will be
3095 -- rejected (see Analyze_Assignment).
3097 Set_Is_Safe_To_Reevaluate
(Id
);
3099 Rewrite
(Original_Bound
, New_Occurrence_Of
(Id
, Loc
));
3101 if Nkind
(Assign
) = N_Assignment_Statement
then
3102 return Expression
(Assign
);
3104 return Original_Bound
;
3108 Hi
: constant Node_Id
:= High_Bound
(R
);
3109 Lo
: constant Node_Id
:= Low_Bound
(R
);
3110 R_Copy
: constant Node_Id
:= New_Copy_Tree
(R
);
3115 -- Start of processing for Process_Bounds
3118 Set_Parent
(R_Copy
, Parent
(R
));
3119 Preanalyze_Range
(R_Copy
);
3120 Typ
:= Etype
(R_Copy
);
3122 -- If the type of the discrete range is Universal_Integer, then the
3123 -- bound's type must be resolved to Integer, and any object used to
3124 -- hold the bound must also have type Integer, unless the literal
3125 -- bounds are constant-folded expressions with a user-defined type.
3127 if Typ
= Universal_Integer
then
3128 if Nkind
(Lo
) = N_Integer_Literal
3129 and then Present
(Etype
(Lo
))
3130 and then Scope
(Etype
(Lo
)) /= Standard_Standard
3134 elsif Nkind
(Hi
) = N_Integer_Literal
3135 and then Present
(Etype
(Hi
))
3136 and then Scope
(Etype
(Hi
)) /= Standard_Standard
3141 Typ
:= Standard_Integer
;
3147 New_Lo
:= One_Bound
(Lo
, Low_Bound
(R_Copy
), Typ
);
3148 New_Hi
:= One_Bound
(Hi
, High_Bound
(R_Copy
), Typ
);
3150 -- Propagate staticness to loop range itself, in case the
3151 -- corresponding subtype is static.
3153 if New_Lo
/= Lo
and then Is_OK_Static_Expression
(New_Lo
) then
3154 Rewrite
(Low_Bound
(R
), New_Copy
(New_Lo
));
3157 if New_Hi
/= Hi
and then Is_OK_Static_Expression
(New_Hi
) then
3158 Rewrite
(High_Bound
(R
), New_Copy
(New_Hi
));
3164 DS
: constant Node_Id
:= Discrete_Subtype_Definition
(N
);
3165 Id
: constant Entity_Id
:= Defining_Identifier
(N
);
3169 -- Start of processing for Analyze_Loop_Parameter_Specification
3174 -- We always consider the loop variable to be referenced, since the loop
3175 -- may be used just for counting purposes.
3177 Generate_Reference
(Id
, N
, ' ');
3179 -- Check for the case of loop variable hiding a local variable (used
3180 -- later on to give a nice warning if the hidden variable is never
3184 H
: constant Entity_Id
:= Homonym
(Id
);
3187 and then Ekind
(H
) = E_Variable
3188 and then Is_Discrete_Type
(Etype
(H
))
3189 and then Enclosing_Dynamic_Scope
(H
) = Enclosing_Dynamic_Scope
(Id
)
3191 Set_Hiding_Loop_Variable
(H
, Id
);
3195 -- Analyze the subtype definition and create temporaries for the bounds.
3196 -- Do not evaluate the range when preanalyzing a quantified expression
3197 -- because bounds expressed as function calls with side effects will be
3198 -- incorrectly replicated.
3200 if Nkind
(DS
) = N_Range
3201 and then Expander_Active
3202 and then Nkind
(Parent
(N
)) /= N_Quantified_Expression
3204 Process_Bounds
(DS
);
3206 -- Either the expander not active or the range of iteration is a subtype
3207 -- indication, an entity, or a function call that yields an aggregate or
3211 DS_Copy
:= New_Copy_Tree
(DS
);
3212 Set_Parent
(DS_Copy
, Parent
(DS
));
3213 Preanalyze_Range
(DS_Copy
);
3215 -- Ada 2012: If the domain of iteration is:
3217 -- a) a function call,
3218 -- b) an identifier that is not a type,
3219 -- c) an attribute reference 'Old (within a postcondition),
3220 -- d) an unchecked conversion or a qualified expression with
3221 -- the proper iterator type.
3223 -- then it is an iteration over a container. It was classified as
3224 -- a loop specification by the parser, and must be rewritten now
3225 -- to activate container iteration. The last case will occur within
3226 -- an expanded inlined call, where the expansion wraps an actual in
3227 -- an unchecked conversion when needed. The expression of the
3228 -- conversion is always an object.
3230 if Nkind
(DS_Copy
) = N_Function_Call
3232 or else (Is_Entity_Name
(DS_Copy
)
3233 and then not Is_Type
(Entity
(DS_Copy
)))
3235 or else (Nkind
(DS_Copy
) = N_Attribute_Reference
3236 and then Attribute_Name
(DS_Copy
) in
3237 Name_Loop_Entry | Name_Old
)
3239 or else Has_Aspect
(Etype
(DS_Copy
), Aspect_Iterable
)
3241 or else Nkind
(DS_Copy
) = N_Unchecked_Type_Conversion
3242 or else (Nkind
(DS_Copy
) = N_Qualified_Expression
3243 and then Is_Iterator
(Etype
(DS_Copy
)))
3245 -- This is an iterator specification. Rewrite it as such and
3246 -- analyze it to capture function calls that may require
3247 -- finalization actions.
3250 I_Spec
: constant Node_Id
:=
3251 Make_Iterator_Specification
(Sloc
(N
),
3252 Defining_Identifier
=> Relocate_Node
(Id
),
3254 Subtype_Indication
=> Empty
,
3255 Reverse_Present
=> Reverse_Present
(N
));
3256 Scheme
: constant Node_Id
:= Parent
(N
);
3259 Set_Iterator_Specification
(Scheme
, I_Spec
);
3260 Set_Loop_Parameter_Specification
(Scheme
, Empty
);
3261 Set_Iterator_Filter
(I_Spec
,
3262 Relocate_Node
(Iterator_Filter
(N
)));
3264 Analyze_Iterator_Specification
(I_Spec
);
3266 -- In a generic context, analyze the original domain of
3267 -- iteration, for name capture.
3269 if not Expander_Active
then
3273 -- Set kind of loop parameter, which may be used in the
3274 -- subsequent analysis of the condition in a quantified
3277 Mutate_Ekind
(Id
, E_Loop_Parameter
);
3281 -- Domain of iteration is not a function call, and is side-effect
3285 -- A quantified expression that appears in a pre/post condition
3286 -- is preanalyzed several times. If the range is given by an
3287 -- attribute reference it is rewritten as a range, and this is
3288 -- done even with expansion disabled. If the type is already set
3289 -- do not reanalyze, because a range with static bounds may be
3290 -- typed Integer by default.
3292 if Nkind
(Parent
(N
)) = N_Quantified_Expression
3293 and then Present
(Etype
(DS
))
3306 -- Some additional checks if we are iterating through a type
3308 if Is_Entity_Name
(DS
)
3309 and then Present
(Entity
(DS
))
3310 and then Is_Type
(Entity
(DS
))
3312 -- The subtype indication may denote the completion of an incomplete
3313 -- type declaration.
3315 if Ekind
(Entity
(DS
)) = E_Incomplete_Type
then
3316 Set_Entity
(DS
, Get_Full_View
(Entity
(DS
)));
3317 Set_Etype
(DS
, Entity
(DS
));
3320 Check_Predicate_Use
(Entity
(DS
));
3323 -- Error if not discrete type
3325 if not Is_Discrete_Type
(Etype
(DS
)) then
3326 Wrong_Type
(DS
, Any_Discrete
);
3327 Set_Etype
(DS
, Any_Type
);
3330 Check_Controlled_Array_Attribute
(DS
);
3332 if Nkind
(DS
) = N_Subtype_Indication
then
3333 Check_Predicate_Use
(Entity
(Subtype_Mark
(DS
)));
3336 if Nkind
(DS
) not in N_Raise_xxx_Error
then
3340 Mutate_Ekind
(Id
, E_Loop_Parameter
);
3342 -- A quantified expression which appears in a pre- or post-condition may
3343 -- be analyzed multiple times. The analysis of the range creates several
3344 -- itypes which reside in different scopes depending on whether the pre-
3345 -- or post-condition has been expanded. Update the type of the loop
3346 -- variable to reflect the proper itype at each stage of analysis.
3348 -- Loop_Nod might not be present when we are preanalyzing a class-wide
3349 -- pre/postcondition since preanalysis occurs in a place unrelated to
3350 -- the actual code and the quantified expression may be the outermost
3351 -- expression of the class-wide condition.
3354 or else Etype
(Id
) = Any_Type
3356 (Present
(Etype
(Id
))
3357 and then Is_Itype
(Etype
(Id
))
3358 and then Present
(Loop_Nod
)
3359 and then Nkind
(Parent
(Loop_Nod
)) = N_Expression_With_Actions
3360 and then Nkind
(Original_Node
(Parent
(Loop_Nod
))) =
3361 N_Quantified_Expression
)
3363 Set_Etype
(Id
, Etype
(DS
));
3366 -- Treat a range as an implicit reference to the type, to inhibit
3367 -- spurious warnings.
3369 Generate_Reference
(Base_Type
(Etype
(DS
)), N
, ' ');
3370 Set_Is_Known_Valid
(Id
, True);
3372 -- The loop is not a declarative part, so the loop variable must be
3373 -- frozen explicitly. Do not freeze while preanalyzing a quantified
3374 -- expression because the freeze node will not be inserted into the
3375 -- tree due to flag Is_Spec_Expression being set.
3377 if Nkind
(Parent
(N
)) /= N_Quantified_Expression
then
3379 Flist
: constant List_Id
:= Freeze_Entity
(Id
, N
);
3381 if Is_Non_Empty_List
(Flist
) then
3382 Insert_Actions
(N
, Flist
);
3387 -- Case where we have a range or a subtype, get type bounds
3389 if Nkind
(DS
) in N_Range | N_Subtype_Indication
3390 and then not Error_Posted
(DS
)
3391 and then Etype
(DS
) /= Any_Type
3392 and then Is_Discrete_Type
(Etype
(DS
))
3397 Null_Range
: Boolean := False;
3400 if Nkind
(DS
) = N_Range
then
3401 L
:= Low_Bound
(DS
);
3402 H
:= High_Bound
(DS
);
3405 Type_Low_Bound
(Underlying_Type
(Etype
(Subtype_Mark
(DS
))));
3407 Type_High_Bound
(Underlying_Type
(Etype
(Subtype_Mark
(DS
))));
3410 -- Check for null or possibly null range and issue warning. We
3411 -- suppress such messages in generic templates and instances,
3412 -- because in practice they tend to be dubious in these cases. The
3413 -- check applies as well to rewritten array element loops where a
3414 -- null range may be detected statically.
3416 if Compile_Time_Compare
(L
, H
, Assume_Valid
=> True) = GT
then
3417 if Compile_Time_Compare
(L
, H
, Assume_Valid
=> False) = GT
then
3418 -- Since we know the range of the loop is always null,
3419 -- set the appropriate flag to remove the loop entirely
3420 -- during expansion.
3422 Set_Is_Null_Loop
(Loop_Nod
);
3426 -- Suppress the warning if inside a generic template or
3427 -- instance, since in practice they tend to be dubious in these
3428 -- cases since they can result from intended parameterization.
3430 if not Inside_A_Generic
and then not In_Instance
then
3432 -- Specialize msg if invalid values could make the loop
3433 -- non-null after all.
3436 if Comes_From_Source
(N
) then
3438 ("??loop range is null, loop will not execute", DS
);
3441 -- Here is where the loop could execute because of
3442 -- invalid values, so issue appropriate message.
3444 elsif Comes_From_Source
(N
) then
3446 ("??loop range may be null, loop may not execute",
3449 ("??can only execute if invalid values are present",
3454 -- In either case, suppress warnings in the body of the loop,
3455 -- since it is likely that these warnings will be inappropriate
3456 -- if the loop never actually executes, which is likely.
3458 Set_Suppress_Loop_Warnings
(Loop_Nod
);
3460 -- The other case for a warning is a reverse loop where the
3461 -- upper bound is the integer literal zero or one, and the
3462 -- lower bound may exceed this value.
3464 -- For example, we have
3466 -- for J in reverse N .. 1 loop
3468 -- In practice, this is very likely to be a case of reversing
3469 -- the bounds incorrectly in the range.
3471 elsif Reverse_Present
(N
)
3472 and then Nkind
(Original_Node
(H
)) = N_Integer_Literal
3474 (Intval
(Original_Node
(H
)) = Uint_0
3476 Intval
(Original_Node
(H
)) = Uint_1
)
3478 -- Lower bound may in fact be known and known not to exceed
3479 -- upper bound (e.g. reverse 0 .. 1) and that's OK.
3481 if Compile_Time_Known_Value
(L
)
3482 and then Expr_Value
(L
) <= Expr_Value
(H
)
3486 -- Otherwise warning is warranted
3489 Error_Msg_N
("??loop range may be null", DS
);
3490 Error_Msg_N
("\??bounds may be wrong way round", DS
);
3494 -- Check if either bound is known to be outside the range of the
3495 -- loop parameter type, this is e.g. the case of a loop from
3496 -- 20..X where the type is 1..19.
3498 -- Such a loop is dubious since either it raises CE or it executes
3499 -- zero times, and that cannot be useful!
3501 if Etype
(DS
) /= Any_Type
3502 and then not Error_Posted
(DS
)
3503 and then Nkind
(DS
) = N_Subtype_Indication
3504 and then Nkind
(Constraint
(DS
)) = N_Range_Constraint
3507 LLo
: constant Node_Id
:=
3508 Low_Bound
(Range_Expression
(Constraint
(DS
)));
3509 LHi
: constant Node_Id
:=
3510 High_Bound
(Range_Expression
(Constraint
(DS
)));
3512 Bad_Bound
: Node_Id
:= Empty
;
3513 -- Suspicious loop bound
3516 -- At this stage L, H are the bounds of the type, and LLo
3517 -- Lhi are the low bound and high bound of the loop.
3519 if Compile_Time_Compare
(LLo
, L
, Assume_Valid
=> True) = LT
3521 Compile_Time_Compare
(LLo
, H
, Assume_Valid
=> True) = GT
3526 if Compile_Time_Compare
(LHi
, L
, Assume_Valid
=> True) = LT
3528 Compile_Time_Compare
(LHi
, H
, Assume_Valid
=> True) = GT
3533 if Present
(Bad_Bound
) then
3535 ("suspicious loop bound out of range of "
3536 & "loop subtype??", Bad_Bound
);
3538 ("\loop executes zero times or raises "
3539 & "Constraint_Error??", Bad_Bound
);
3542 if Compile_Time_Compare
(LLo
, LHi
, Assume_Valid
=> False)
3545 Error_Msg_N
("??constrained range is null",
3548 -- Additional constraints on modular types can be
3549 -- confusing, add more information.
3551 if Ekind
(Etype
(DS
)) = E_Modular_Integer_Subtype
then
3552 Error_Msg_Uint_1
:= Intval
(LLo
);
3553 Error_Msg_Uint_2
:= Intval
(LHi
);
3554 Error_Msg_NE
("\iterator has modular type &, " &
3555 "so the loop has bounds ^ ..^",
3560 Set_Is_Null_Loop
(Loop_Nod
);
3563 -- Suppress other warnigns about the body of the loop, as
3564 -- it will never execute.
3565 Set_Suppress_Loop_Warnings
(Loop_Nod
);
3570 -- This declare block is about warnings, if we get an exception while
3571 -- testing for warnings, we simply abandon the attempt silently. This
3572 -- most likely occurs as the result of a previous error, but might
3573 -- just be an obscure case we have missed. In either case, not giving
3574 -- the warning is perfectly acceptable.
3578 -- With debug flag K we will get an exception unless an error
3579 -- has already occurred (useful for debugging).
3581 if Debug_Flag_K
then
3582 Check_Error_Detected
;
3587 if Present
(Iterator_Filter
(N
)) then
3588 Analyze_And_Resolve
(Iterator_Filter
(N
), Standard_Boolean
);
3591 -- A loop parameter cannot be effectively volatile (SPARK RM 7.1.3(4)).
3592 -- This check is relevant only when SPARK_Mode is on as it is not a
3593 -- standard Ada legality check.
3595 if SPARK_Mode
= On
and then Is_Effectively_Volatile
(Id
) then
3596 Error_Msg_N
("loop parameter cannot be volatile", Id
);
3598 end Analyze_Loop_Parameter_Specification
;
3600 ----------------------------
3601 -- Analyze_Loop_Statement --
3602 ----------------------------
3604 procedure Analyze_Loop_Statement
(N
: Node_Id
) is
3606 -- The following exception is raised by routine Prepare_Loop_Statement
3607 -- to avoid further analysis of a transformed loop.
3609 procedure Prepare_Loop_Statement
3611 Stop_Processing
: out Boolean);
3612 -- Determine whether loop statement N with iteration scheme Iter must be
3613 -- transformed prior to analysis, and if so, perform it.
3614 -- If Stop_Processing is set to True, should stop further processing.
3616 ----------------------------
3617 -- Prepare_Loop_Statement --
3618 ----------------------------
3620 procedure Prepare_Loop_Statement
3622 Stop_Processing
: out Boolean)
3624 function Has_Sec_Stack_Default_Iterator
3625 (Cont_Typ
: Entity_Id
) return Boolean;
3626 pragma Inline
(Has_Sec_Stack_Default_Iterator
);
3627 -- Determine whether container type Cont_Typ has a default iterator
3628 -- that requires secondary stack management.
3630 function Is_Sec_Stack_Iteration_Primitive
3631 (Cont_Typ
: Entity_Id
;
3632 Iter_Prim_Nam
: Name_Id
) return Boolean;
3633 pragma Inline
(Is_Sec_Stack_Iteration_Primitive
);
3634 -- Determine whether container type Cont_Typ has an iteration routine
3635 -- described by its name Iter_Prim_Nam that requires secondary stack
3638 function Is_Wrapped_In_Block
(Stmt
: Node_Id
) return Boolean;
3639 pragma Inline
(Is_Wrapped_In_Block
);
3640 -- Determine whether arbitrary statement Stmt is the sole statement
3641 -- wrapped within some block, excluding pragmas.
3643 procedure Prepare_Iterator_Loop
3644 (Iter_Spec
: Node_Id
;
3645 Stop_Processing
: out Boolean);
3646 pragma Inline
(Prepare_Iterator_Loop
);
3647 -- Prepare an iterator loop with iteration specification Iter_Spec
3648 -- for transformation if needed.
3649 -- If Stop_Processing is set to True, should stop further processing.
3651 procedure Prepare_Param_Spec_Loop
3652 (Param_Spec
: Node_Id
;
3653 Stop_Processing
: out Boolean);
3654 pragma Inline
(Prepare_Param_Spec_Loop
);
3655 -- Prepare a discrete loop with parameter specification Param_Spec
3656 -- for transformation if needed.
3657 -- If Stop_Processing is set to True, should stop further processing.
3659 procedure Wrap_Loop_Statement
(Manage_Sec_Stack
: Boolean);
3660 pragma Inline
(Wrap_Loop_Statement
);
3661 -- Wrap loop statement N within a block. Flag Manage_Sec_Stack must
3662 -- be set when the block must mark and release the secondary stack.
3663 -- Should stop further processing after calling this procedure.
3665 ------------------------------------
3666 -- Has_Sec_Stack_Default_Iterator --
3667 ------------------------------------
3669 function Has_Sec_Stack_Default_Iterator
3670 (Cont_Typ
: Entity_Id
) return Boolean
3672 Def_Iter
: constant Node_Id
:=
3673 Find_Value_Of_Aspect
3674 (Cont_Typ
, Aspect_Default_Iterator
);
3678 and then Requires_Transient_Scope
(Etype
(Def_Iter
));
3679 end Has_Sec_Stack_Default_Iterator
;
3681 --------------------------------------
3682 -- Is_Sec_Stack_Iteration_Primitive --
3683 --------------------------------------
3685 function Is_Sec_Stack_Iteration_Primitive
3686 (Cont_Typ
: Entity_Id
;
3687 Iter_Prim_Nam
: Name_Id
) return Boolean
3689 Iter_Prim
: constant Entity_Id
:=
3690 Get_Iterable_Type_Primitive
3691 (Cont_Typ
, Iter_Prim_Nam
);
3695 and then Requires_Transient_Scope
(Etype
(Iter_Prim
));
3696 end Is_Sec_Stack_Iteration_Primitive
;
3698 -------------------------
3699 -- Is_Wrapped_In_Block --
3700 -------------------------
3702 function Is_Wrapped_In_Block
(Stmt
: Node_Id
) return Boolean is
3708 Blk_Id
:= Current_Scope
;
3710 -- The current context is a block. Inspect the statements of the
3711 -- block to determine whether it wraps Stmt.
3713 if Ekind
(Blk_Id
) = E_Block
3714 and then Present
(Block_Node
(Blk_Id
))
3717 Handled_Statement_Sequence
(Parent
(Block_Node
(Blk_Id
)));
3719 -- Skip leading pragmas introduced for invariant and predicate
3722 Blk_Stmt
:= First
(Statements
(Blk_HSS
));
3723 while Present
(Blk_Stmt
)
3724 and then Nkind
(Blk_Stmt
) = N_Pragma
3729 return Blk_Stmt
= Stmt
and then No
(Next
(Blk_Stmt
));
3733 end Is_Wrapped_In_Block
;
3735 ---------------------------
3736 -- Prepare_Iterator_Loop --
3737 ---------------------------
3739 procedure Prepare_Iterator_Loop
3740 (Iter_Spec
: Node_Id
;
3741 Stop_Processing
: out Boolean)
3743 Cont_Typ
: Entity_Id
;
3748 Stop_Processing
:= False;
3750 -- The iterator specification has syntactic errors. Transform the
3751 -- loop into an infinite loop in order to safely perform at least
3752 -- some minor analysis. This check must come first.
3754 if Error_Posted
(Iter_Spec
) then
3755 Set_Iteration_Scheme
(N
, Empty
);
3757 Stop_Processing
:= True;
3759 -- Nothing to do when the loop is already wrapped in a block
3761 elsif Is_Wrapped_In_Block
(N
) then
3764 -- Otherwise the iterator loop traverses an array or a container
3765 -- and appears in the form
3767 -- for Def_Id in [reverse] Iterator_Name loop
3768 -- for Def_Id [: Subtyp_Indic] of [reverse] Iterable_Name loop
3771 -- Prepare a copy of the iterated name for preanalysis. The
3772 -- copy is semi inserted into the tree by setting its Parent
3775 Nam
:= Name
(Iter_Spec
);
3776 Nam_Copy
:= New_Copy_Tree
(Nam
);
3777 Set_Parent
(Nam_Copy
, Parent
(Nam
));
3779 -- Determine what the loop is iterating on
3781 Preanalyze_Range
(Nam_Copy
);
3782 Cont_Typ
:= Etype
(Nam_Copy
);
3784 -- The iterator loop is traversing an array. This case does not
3785 -- require any transformation.
3787 if Is_Array_Type
(Cont_Typ
) then
3790 -- Otherwise unconditionally wrap the loop statement within
3791 -- a block. The expansion of iterator loops may relocate the
3792 -- iterator outside the loop, thus "leaking" its entity into
3793 -- the enclosing scope. Wrapping the loop statement allows
3794 -- for multiple iterator loops using the same iterator name
3795 -- to coexist within the same scope.
3797 -- The block must manage the secondary stack when the iterator
3798 -- loop is traversing a container using either
3800 -- * A default iterator obtained on the secondary stack
3802 -- * Call to Iterate where the iterator is returned on the
3805 -- * Combination of First, Next, and Has_Element where the
3806 -- first two return a cursor on the secondary stack.
3810 (Manage_Sec_Stack
=>
3811 Has_Sec_Stack_Default_Iterator
(Cont_Typ
)
3812 or else Has_Sec_Stack_Call
(Nam_Copy
)
3813 or else Is_Sec_Stack_Iteration_Primitive
3814 (Cont_Typ
, Name_First
)
3815 or else Is_Sec_Stack_Iteration_Primitive
3816 (Cont_Typ
, Name_Next
));
3817 Stop_Processing
:= True;
3820 end Prepare_Iterator_Loop
;
3822 -----------------------------
3823 -- Prepare_Param_Spec_Loop --
3824 -----------------------------
3826 procedure Prepare_Param_Spec_Loop
3827 (Param_Spec
: Node_Id
;
3828 Stop_Processing
: out Boolean)
3834 Rng_Typ
: Entity_Id
;
3837 Stop_Processing
:= False;
3838 Rng
:= Discrete_Subtype_Definition
(Param_Spec
);
3840 -- Nothing to do when the loop is already wrapped in a block
3842 if Is_Wrapped_In_Block
(N
) then
3845 -- The parameter specification appears in the form
3847 -- for Def_Id in Subtype_Mark Constraint loop
3849 elsif Nkind
(Rng
) = N_Subtype_Indication
3850 and then Nkind
(Range_Expression
(Constraint
(Rng
))) = N_Range
3852 Rng
:= Range_Expression
(Constraint
(Rng
));
3854 -- Preanalyze the bounds of the range constraint, setting
3855 -- parent fields to associate the copied bounds with the range,
3856 -- allowing proper tree climbing during preanalysis.
3858 Low
:= New_Copy_Tree
(Low_Bound
(Rng
));
3859 High
:= New_Copy_Tree
(High_Bound
(Rng
));
3861 Set_Parent
(Low
, Rng
);
3862 Set_Parent
(High
, Rng
);
3867 -- The bounds contain at least one function call that returns
3868 -- on the secondary stack. Note that the loop must be wrapped
3869 -- only when such a call exists.
3871 if Has_Sec_Stack_Call
(Low
) or else Has_Sec_Stack_Call
(High
)
3873 Wrap_Loop_Statement
(Manage_Sec_Stack
=> True);
3874 Stop_Processing
:= True;
3877 -- Otherwise the parameter specification appears in the form
3879 -- for Def_Id in Range loop
3882 -- Prepare a copy of the discrete range for preanalysis. The
3883 -- copy is semi inserted into the tree by setting its Parent
3886 Rng_Copy
:= New_Copy_Tree
(Rng
);
3887 Set_Parent
(Rng_Copy
, Parent
(Rng
));
3889 -- Determine what the loop is iterating on
3891 Preanalyze_Range
(Rng_Copy
);
3892 Rng_Typ
:= Etype
(Rng_Copy
);
3894 -- Wrap the loop statement within a block in order to manage
3895 -- the secondary stack when the discrete range is
3897 -- * Either a Forward_Iterator or a Reverse_Iterator
3899 -- * Function call whose return type requires finalization
3902 -- ??? it is unclear why using Has_Sec_Stack_Call directly on
3903 -- the discrete range causes the freeze node of an itype to be
3904 -- in the wrong scope in complex assertion expressions.
3906 if Is_Iterator
(Rng_Typ
)
3907 or else (Nkind
(Rng_Copy
) = N_Function_Call
3908 and then Needs_Finalization
(Rng_Typ
))
3910 Wrap_Loop_Statement
(Manage_Sec_Stack
=> True);
3911 Stop_Processing
:= True;
3914 end Prepare_Param_Spec_Loop
;
3916 -------------------------
3917 -- Wrap_Loop_Statement --
3918 -------------------------
3920 procedure Wrap_Loop_Statement
(Manage_Sec_Stack
: Boolean) is
3921 Loc
: constant Source_Ptr
:= Sloc
(N
);
3928 Make_Block_Statement
(Loc
,
3929 Declarations
=> New_List
,
3930 Handled_Statement_Sequence
=>
3931 Make_Handled_Sequence_Of_Statements
(Loc
,
3932 Statements
=> New_List
(Relocate_Node
(N
))));
3934 Add_Block_Identifier
(Blk
, Blk_Id
);
3935 Set_Uses_Sec_Stack
(Blk_Id
, Manage_Sec_Stack
);
3939 end Wrap_Loop_Statement
;
3943 Iter_Spec
: constant Node_Id
:= Iterator_Specification
(Iter
);
3944 Param_Spec
: constant Node_Id
:= Loop_Parameter_Specification
(Iter
);
3946 -- Start of processing for Prepare_Loop_Statement
3949 Stop_Processing
:= False;
3951 if Present
(Iter_Spec
) then
3952 Prepare_Iterator_Loop
(Iter_Spec
, Stop_Processing
);
3954 elsif Present
(Param_Spec
) then
3955 Prepare_Param_Spec_Loop
(Param_Spec
, Stop_Processing
);
3957 end Prepare_Loop_Statement
;
3959 -- Local declarations
3961 Id
: constant Node_Id
:= Identifier
(N
);
3962 Iter
: constant Node_Id
:= Iteration_Scheme
(N
);
3963 Loc
: constant Source_Ptr
:= Sloc
(N
);
3967 -- Start of processing for Analyze_Loop_Statement
3970 if Present
(Id
) then
3972 -- Make name visible, e.g. for use in exit statements. Loop labels
3973 -- are always considered to be referenced.
3978 -- Guard against serious error (typically, a scope mismatch when
3979 -- semantic analysis is requested) by creating loop entity to
3980 -- continue analysis.
3983 if Total_Errors_Detected
/= 0 then
3984 Ent
:= New_Internal_Entity
(E_Loop
, Current_Scope
, Loc
, 'L');
3986 raise Program_Error
;
3989 -- Verify that the loop name is hot hidden by an unrelated
3990 -- declaration in an inner scope.
3992 elsif Ekind
(Ent
) /= E_Label
and then Ekind
(Ent
) /= E_Loop
then
3993 Error_Msg_Sloc
:= Sloc
(Ent
);
3994 Error_Msg_N
("implicit label declaration for & is hidden#", Id
);
3996 if Present
(Homonym
(Ent
))
3997 and then Ekind
(Homonym
(Ent
)) = E_Label
3999 Set_Entity
(Id
, Ent
);
4000 Mutate_Ekind
(Ent
, E_Loop
);
4004 Generate_Reference
(Ent
, N
, ' ');
4005 Generate_Definition
(Ent
);
4007 -- If we found a label, mark its type. If not, ignore it, since it
4008 -- means we have a conflicting declaration, which would already
4009 -- have been diagnosed at declaration time. Set Label_Construct
4010 -- of the implicit label declaration, which is not created by the
4011 -- parser for generic units.
4013 if Ekind
(Ent
) = E_Label
then
4014 Reinit_Field_To_Zero
(Ent
, F_Enclosing_Scope
);
4015 Mutate_Ekind
(Ent
, E_Loop
);
4017 if Nkind
(Parent
(Ent
)) = N_Implicit_Label_Declaration
then
4018 Set_Label_Construct
(Parent
(Ent
), N
);
4023 -- Case of no identifier present. Create one and attach it to the
4024 -- loop statement for use as a scope and as a reference for later
4025 -- expansions. Indicate that the label does not come from source,
4026 -- and attach it to the loop statement so it is part of the tree,
4027 -- even without a full declaration.
4030 Ent
:= New_Internal_Entity
(E_Loop
, Current_Scope
, Loc
, 'L');
4031 Set_Etype
(Ent
, Standard_Void_Type
);
4032 Set_Identifier
(N
, New_Occurrence_Of
(Ent
, Loc
));
4033 Set_Parent
(Ent
, N
);
4034 Set_Has_Created_Identifier
(N
);
4037 -- Determine whether the loop statement must be transformed prior to
4038 -- analysis, and if so, perform it. This early modification is needed
4041 -- * The loop has an erroneous iteration scheme. In this case the
4042 -- loop is converted into an infinite loop in order to perform
4045 -- * The loop is an Ada 2012 iterator loop. In this case the loop is
4046 -- wrapped within a block to provide a local scope for the iterator.
4047 -- If the iterator specification requires the secondary stack in any
4048 -- way, the block is marked in order to manage it.
4050 -- * The loop is using a parameter specification where the discrete
4051 -- range requires the secondary stack. In this case the loop is
4052 -- wrapped within a block in order to manage the secondary stack.
4054 if Present
(Iter
) then
4056 Stop_Processing
: Boolean;
4058 Prepare_Loop_Statement
(Iter
, Stop_Processing
);
4060 if Stop_Processing
then
4066 -- Kill current values on entry to loop, since statements in the body of
4067 -- the loop may have been executed before the loop is entered. Similarly
4068 -- we kill values after the loop, since we do not know that the body of
4069 -- the loop was executed.
4071 Kill_Current_Values
;
4073 Analyze_Iteration_Scheme
(Iter
);
4075 -- Check for following case which merits a warning if the type E of is
4076 -- a multi-dimensional array (and no explicit subscript ranges present).
4082 and then Present
(Loop_Parameter_Specification
(Iter
))
4085 LPS
: constant Node_Id
:= Loop_Parameter_Specification
(Iter
);
4086 DSD
: constant Node_Id
:=
4087 Original_Node
(Discrete_Subtype_Definition
(LPS
));
4089 if Nkind
(DSD
) = N_Attribute_Reference
4090 and then Attribute_Name
(DSD
) = Name_Range
4091 and then No
(Expressions
(DSD
))
4094 Typ
: constant Entity_Id
:= Etype
(Prefix
(DSD
));
4096 if Is_Array_Type
(Typ
)
4097 and then Number_Dimensions
(Typ
) > 1
4098 and then Nkind
(Parent
(N
)) = N_Loop_Statement
4099 and then Present
(Iteration_Scheme
(Parent
(N
)))
4102 OIter
: constant Node_Id
:=
4103 Iteration_Scheme
(Parent
(N
));
4104 OLPS
: constant Node_Id
:=
4105 Loop_Parameter_Specification
(OIter
);
4106 ODSD
: constant Node_Id
:=
4107 Original_Node
(Discrete_Subtype_Definition
(OLPS
));
4109 if Nkind
(ODSD
) = N_Attribute_Reference
4110 and then Attribute_Name
(ODSD
) = Name_Range
4111 and then No
(Expressions
(ODSD
))
4112 and then Etype
(Prefix
(ODSD
)) = Typ
4114 Error_Msg_Sloc
:= Sloc
(ODSD
);
4116 ("inner range same as outer range#??", DSD
);
4125 -- Analyze the statements of the body except in the case of an Ada 2012
4126 -- iterator with the expander active. In this case the expander will do
4127 -- a rewrite of the loop into a while loop. We will then analyze the
4128 -- loop body when we analyze this while loop.
4130 -- We need to do this delay because if the container is for indefinite
4131 -- types the actual subtype of the components will only be determined
4132 -- when the cursor declaration is analyzed.
4134 -- If the expander is not active then we want to analyze the loop body
4135 -- now even in the Ada 2012 iterator case, since the rewriting will not
4136 -- be done. Insert the loop variable in the current scope, if not done
4137 -- when analysing the iteration scheme. Set its kind properly to detect
4138 -- improper uses in the loop body.
4140 -- In GNATprove mode, we do one of the above depending on the kind of
4141 -- loop. If it is an iterator over an array, then we do not analyze the
4142 -- loop now. We will analyze it after it has been rewritten by the
4143 -- special SPARK expansion which is activated in GNATprove mode. We need
4144 -- to do this so that other expansions that should occur in GNATprove
4145 -- mode take into account the specificities of the rewritten loop, in
4146 -- particular the introduction of a renaming (which needs to be
4149 -- In other cases in GNATprove mode then we want to analyze the loop
4150 -- body now, since no rewriting will occur. Within a generic the
4151 -- GNATprove mode is irrelevant, we must analyze the generic for
4152 -- non-local name capture.
4155 and then Present
(Iterator_Specification
(Iter
))
4158 and then Is_Iterator_Over_Array
(Iterator_Specification
(Iter
))
4159 and then not Inside_A_Generic
4163 elsif not Expander_Active
then
4165 I_Spec
: constant Node_Id
:= Iterator_Specification
(Iter
);
4166 Id
: constant Entity_Id
:= Defining_Identifier
(I_Spec
);
4169 if Scope
(Id
) /= Current_Scope
then
4173 -- In an element iterator, the loop parameter is a variable if
4174 -- the domain of iteration (container or array) is a variable.
4176 if not Of_Present
(I_Spec
)
4177 or else not Is_Variable
(Name
(I_Spec
))
4179 Mutate_Ekind
(Id
, E_Loop_Parameter
);
4183 Analyze_Statements
(Statements
(N
));
4187 -- Pre-Ada2012 for-loops and while loops
4189 Analyze_Statements
(Statements
(N
));
4192 -- If the loop has no side effects, mark it for removal.
4194 if Side_Effect_Free_Loop
(N
) then
4195 Set_Is_Null_Loop
(N
);
4198 -- When the iteration scheme of a loop contains attribute 'Loop_Entry,
4199 -- the loop is transformed into a conditional block. Retrieve the loop.
4203 if Subject_To_Loop_Entry_Attributes
(Stmt
) then
4204 Stmt
:= Find_Loop_In_Conditional_Block
(Stmt
);
4207 -- Finish up processing for the loop. We kill all current values, since
4208 -- in general we don't know if the statements in the loop have been
4209 -- executed. We could do a bit better than this with a loop that we
4210 -- know will execute at least once, but it's not worth the trouble and
4211 -- the front end is not in the business of flow tracing.
4213 Process_End_Label
(Stmt
, 'e', Ent
);
4215 Kill_Current_Values
;
4217 -- Check for infinite loop. Skip check for generated code, since it
4218 -- justs waste time and makes debugging the routine called harder.
4220 -- Note that we have to wait till the body of the loop is fully analyzed
4221 -- before making this call, since Check_Infinite_Loop_Warning relies on
4222 -- being able to use semantic visibility information to find references.
4224 if Comes_From_Source
(Stmt
) then
4225 Check_Infinite_Loop_Warning
(Stmt
);
4228 -- Code after loop is unreachable if the loop has no WHILE or FOR and
4229 -- contains no EXIT statements within the body of the loop.
4231 if No
(Iter
) and then not Has_Exit
(Ent
) then
4232 Check_Unreachable_Code
(Stmt
);
4234 end Analyze_Loop_Statement
;
4236 ----------------------------
4237 -- Analyze_Null_Statement --
4238 ----------------------------
4240 -- Note: the semantics of the null statement is implemented by a single
4241 -- null statement, too bad everything isn't as simple as this.
4243 procedure Analyze_Null_Statement
(N
: Node_Id
) is
4244 pragma Warnings
(Off
, N
);
4247 end Analyze_Null_Statement
;
4249 -------------------------
4250 -- Analyze_Target_Name --
4251 -------------------------
4253 procedure Analyze_Target_Name
(N
: Node_Id
) is
4254 procedure Report_Error
;
4255 -- Complain about illegal use of target_name and rewrite it into unknown
4262 procedure Report_Error
is
4265 ("must appear in the right-hand side of an assignment statement",
4267 Rewrite
(N
, New_Occurrence_Of
(Any_Id
, Sloc
(N
)));
4270 -- Start of processing for Analyze_Target_Name
4273 -- A target name has the type of the left-hand side of the enclosing
4276 -- First, verify that the context is the right-hand side of an
4277 -- assignment statement.
4279 if No
(Current_Assignment
) then
4285 Current
: Node_Id
:= N
;
4286 Context
: Node_Id
:= Parent
(N
);
4288 while Present
(Context
) loop
4290 -- Check if target_name appears in the expression of the enclosing
4293 if Nkind
(Context
) = N_Assignment_Statement
then
4294 if Current
= Expression
(Context
) then
4295 pragma Assert
(Context
= Current_Assignment
);
4296 Set_Etype
(N
, Etype
(Name
(Current_Assignment
)));
4302 -- Prevent the search from going too far
4304 elsif Is_Body_Or_Package_Declaration
(Context
) then
4310 Context
:= Parent
(Context
);
4315 end Analyze_Target_Name
;
4317 ------------------------
4318 -- Analyze_Statements --
4319 ------------------------
4321 procedure Analyze_Statements
(L
: List_Id
) is
4326 -- The labels declared in the statement list are reachable from
4327 -- statements in the list. We do this as a prepass so that any goto
4328 -- statement will be properly flagged if its target is not reachable.
4329 -- This is not required, but is nice behavior.
4332 while Present
(S
) loop
4333 if Nkind
(S
) = N_Label
then
4334 Analyze
(Identifier
(S
));
4335 Lab
:= Entity
(Identifier
(S
));
4337 -- If we found a label mark it as reachable
4339 if Ekind
(Lab
) = E_Label
then
4340 Generate_Definition
(Lab
);
4341 Set_Reachable
(Lab
);
4343 if Nkind
(Parent
(Lab
)) = N_Implicit_Label_Declaration
then
4344 Set_Label_Construct
(Parent
(Lab
), S
);
4347 -- If we failed to find a label, it means the implicit declaration
4348 -- of the label was hidden. A for-loop parameter can do this to
4349 -- a label with the same name inside the loop, since the implicit
4350 -- label declaration is in the innermost enclosing body or block
4354 Error_Msg_Sloc
:= Sloc
(Lab
);
4356 ("implicit label declaration for & is hidden#",
4364 -- Perform semantic analysis on all statements
4366 Conditional_Statements_Begin
;
4369 while Present
(S
) loop
4372 -- Remove dimension in all statements
4374 Remove_Dimension_In_Statement
(S
);
4378 Conditional_Statements_End
;
4380 -- Make labels unreachable. Visibility is not sufficient, because labels
4381 -- in one if-branch for example are not reachable from the other branch,
4382 -- even though their declarations are in the enclosing declarative part.
4385 while Present
(S
) loop
4386 if Nkind
(S
) = N_Label
then
4387 Set_Reachable
(Entity
(Identifier
(S
)), False);
4392 end Analyze_Statements
;
4394 ----------------------------
4395 -- Check_Unreachable_Code --
4396 ----------------------------
4398 procedure Check_Unreachable_Code
(N
: Node_Id
) is
4399 Error_Node
: Node_Id
;
4403 if Is_List_Member
(N
) and then Comes_From_Source
(N
) then
4408 Nxt
:= Original_Node
(Next
(N
));
4410 -- Skip past pragmas
4412 while Nkind
(Nxt
) = N_Pragma
loop
4413 Nxt
:= Original_Node
(Next
(Nxt
));
4416 -- If a label follows us, then we never have dead code, since
4417 -- someone could branch to the label, so we just ignore it.
4419 if Nkind
(Nxt
) = N_Label
then
4422 -- Otherwise see if we have a real statement following us
4425 and then Comes_From_Source
(Nxt
)
4426 and then Is_Statement
(Nxt
)
4428 -- Special very annoying exception. If we have a return that
4429 -- follows a raise, then we allow it without a warning, since
4430 -- the Ada RM annoyingly requires a useless return here.
4432 if Nkind
(Original_Node
(N
)) /= N_Raise_Statement
4433 or else Nkind
(Nxt
) /= N_Simple_Return_Statement
4435 -- The rather strange shenanigans with the warning message
4436 -- here reflects the fact that Kill_Dead_Code is very good
4437 -- at removing warnings in deleted code, and this is one
4438 -- warning we would prefer NOT to have removed.
4442 -- If we have unreachable code, analyze and remove the
4443 -- unreachable code, since it is useless and we don't
4444 -- want to generate junk warnings.
4446 -- We skip this step if we are not in code generation mode
4447 -- or CodePeer mode.
4449 -- This is the one case where we remove dead code in the
4450 -- semantics as opposed to the expander, and we do not want
4451 -- to remove code if we are not in code generation mode,
4452 -- since this messes up the tree or loses useful information
4455 -- Note that one might react by moving the whole circuit to
4456 -- exp_ch5, but then we lose the warning in -gnatc mode.
4458 if Operating_Mode
= Generate_Code
4459 and then not CodePeer_Mode
4464 -- Quit deleting when we have nothing more to delete
4465 -- or if we hit a label (since someone could transfer
4466 -- control to a label, so we should not delete it).
4468 exit when No
(Nxt
) or else Nkind
(Nxt
) = N_Label
;
4470 -- Statement/declaration is to be deleted
4474 Kill_Dead_Code
(Nxt
);
4479 ("??unreachable code!", Sloc
(Error_Node
), Error_Node
);
4482 -- If the unconditional transfer of control instruction is the
4483 -- last statement of a sequence, then see if our parent is one of
4484 -- the constructs for which we count unblocked exits, and if so,
4485 -- adjust the count.
4490 -- Statements in THEN part or ELSE part of IF statement
4492 if Nkind
(P
) = N_If_Statement
then
4495 -- Statements in ELSIF part of an IF statement
4497 elsif Nkind
(P
) = N_Elsif_Part
then
4499 pragma Assert
(Nkind
(P
) = N_If_Statement
);
4501 -- Statements in CASE statement alternative
4503 elsif Nkind
(P
) = N_Case_Statement_Alternative
then
4505 pragma Assert
(Nkind
(P
) = N_Case_Statement
);
4507 -- Statements in body of block
4509 elsif Nkind
(P
) = N_Handled_Sequence_Of_Statements
4510 and then Nkind
(Parent
(P
)) = N_Block_Statement
4512 -- The original loop is now placed inside a block statement
4513 -- due to the expansion of attribute 'Loop_Entry. Return as
4514 -- this is not a "real" block for the purposes of exit
4517 if Nkind
(N
) = N_Loop_Statement
4518 and then Subject_To_Loop_Entry_Attributes
(N
)
4523 -- Statements in exception handler in a block
4525 elsif Nkind
(P
) = N_Exception_Handler
4526 and then Nkind
(Parent
(P
)) = N_Handled_Sequence_Of_Statements
4527 and then Nkind
(Parent
(Parent
(P
))) = N_Block_Statement
4531 -- None of these cases, so return
4537 -- This was one of the cases we are looking for (i.e. the
4538 -- parent construct was IF, CASE or block) so decrement count.
4540 Unblocked_Exit_Count
:= Unblocked_Exit_Count
- 1;
4544 end Check_Unreachable_Code
;
4546 ------------------------
4547 -- Has_Sec_Stack_Call --
4548 ------------------------
4550 function Has_Sec_Stack_Call
(N
: Node_Id
) return Boolean is
4551 function Check_Call
(N
: Node_Id
) return Traverse_Result
;
4552 -- Check if N is a function call which uses the secondary stack
4558 function Check_Call
(N
: Node_Id
) return Traverse_Result
is
4564 if Nkind
(N
) = N_Function_Call
then
4567 -- Obtain the subprogram being invoked
4570 if Nkind
(Nam
) = N_Explicit_Dereference
then
4571 Nam
:= Prefix
(Nam
);
4573 elsif Nkind
(Nam
) = N_Selected_Component
then
4574 Nam
:= Selector_Name
(Nam
);
4581 Subp
:= Entity
(Nam
);
4583 if Present
(Subp
) then
4584 Typ
:= Etype
(Subp
);
4586 if Requires_Transient_Scope
(Typ
) then
4589 elsif Sec_Stack_Needed_For_Return
(Subp
) then
4595 -- Continue traversing the tree
4600 function Check_Calls
is new Traverse_Func
(Check_Call
);
4602 -- Start of processing for Has_Sec_Stack_Call
4605 return Check_Calls
(N
) = Abandon
;
4606 end Has_Sec_Stack_Call
;
4608 ----------------------
4609 -- Preanalyze_Range --
4610 ----------------------
4612 procedure Preanalyze_Range
(R_Copy
: Node_Id
) is
4613 Save_Analysis
: constant Boolean := Full_Analysis
;
4617 Full_Analysis
:= False;
4618 Expander_Mode_Save_And_Set
(False);
4620 -- In addition to the above we must explicitly suppress the generation
4621 -- of freeze nodes that might otherwise be generated during resolution
4622 -- of the range (e.g. if given by an attribute that will freeze its
4625 Set_Must_Not_Freeze
(R_Copy
);
4627 if Nkind
(R_Copy
) = N_Attribute_Reference
then
4628 Set_Must_Not_Freeze
(Prefix
(R_Copy
));
4633 if Nkind
(R_Copy
) in N_Subexpr
and then Is_Overloaded
(R_Copy
) then
4635 -- Apply preference rules for range of predefined integer types, or
4636 -- check for array or iterable construct for "of" iterator, or
4637 -- diagnose true ambiguity.
4642 Found
: Entity_Id
:= Empty
;
4645 Get_First_Interp
(R_Copy
, I
, It
);
4646 while Present
(It
.Typ
) loop
4647 if Is_Discrete_Type
(It
.Typ
) then
4651 if Scope
(Found
) = Standard_Standard
then
4654 elsif Scope
(It
.Typ
) = Standard_Standard
then
4658 -- Both of them are user-defined
4661 ("ambiguous bounds in range of iteration", R_Copy
);
4662 Error_Msg_N
("\possible interpretations:", R_Copy
);
4663 Error_Msg_NE
("\\}", R_Copy
, Found
);
4664 Error_Msg_NE
("\\}", R_Copy
, It
.Typ
);
4669 elsif Nkind
(Parent
(R_Copy
)) = N_Iterator_Specification
4670 and then Of_Present
(Parent
(R_Copy
))
4672 if Is_Array_Type
(It
.Typ
)
4673 or else Has_Aspect
(It
.Typ
, Aspect_Iterator_Element
)
4674 or else Has_Aspect
(It
.Typ
, Aspect_Constant_Indexing
)
4675 or else Has_Aspect
(It
.Typ
, Aspect_Variable_Indexing
)
4679 Set_Etype
(R_Copy
, It
.Typ
);
4682 Error_Msg_N
("ambiguous domain of iteration", R_Copy
);
4687 Get_Next_Interp
(I
, It
);
4692 -- Subtype mark in iteration scheme
4694 if Is_Entity_Name
(R_Copy
) and then Is_Type
(Entity
(R_Copy
)) then
4697 -- Expression in range, or Ada 2012 iterator
4699 elsif Nkind
(R_Copy
) in N_Subexpr
then
4701 Typ
:= Etype
(R_Copy
);
4703 if Is_Discrete_Type
(Typ
) then
4706 -- Check that the resulting object is an iterable container
4708 elsif Has_Aspect
(Typ
, Aspect_Iterator_Element
)
4709 or else Has_Aspect
(Typ
, Aspect_Constant_Indexing
)
4710 or else Has_Aspect
(Typ
, Aspect_Variable_Indexing
)
4714 -- The expression may yield an implicit reference to an iterable
4715 -- container. Insert explicit dereference so that proper type is
4716 -- visible in the loop.
4718 elsif Has_Implicit_Dereference
(Etype
(R_Copy
)) then
4719 Build_Explicit_Dereference
4720 (R_Copy
, Get_Reference_Discriminant
(Etype
(R_Copy
)));
4724 Expander_Mode_Restore
;
4725 Full_Analysis
:= Save_Analysis
;
4726 end Preanalyze_Range
;