1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2016, 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 Einfo
; use Einfo
;
30 with Errout
; use Errout
;
31 with Expander
; use Expander
;
32 with Exp_Ch6
; use Exp_Ch6
;
33 with Exp_Util
; use Exp_Util
;
34 with Freeze
; use Freeze
;
35 with Ghost
; use Ghost
;
37 with Lib
.Xref
; use Lib
.Xref
;
38 with Namet
; use Namet
;
39 with Nlists
; use Nlists
;
40 with Nmake
; use Nmake
;
42 with Restrict
; use Restrict
;
43 with Rident
; use Rident
;
45 with Sem_Aux
; use Sem_Aux
;
46 with Sem_Case
; use Sem_Case
;
47 with Sem_Ch3
; use Sem_Ch3
;
48 with Sem_Ch6
; use Sem_Ch6
;
49 with Sem_Ch8
; use Sem_Ch8
;
50 with Sem_Dim
; use Sem_Dim
;
51 with Sem_Disp
; use Sem_Disp
;
52 with Sem_Elab
; use Sem_Elab
;
53 with Sem_Eval
; use Sem_Eval
;
54 with Sem_Res
; use Sem_Res
;
55 with Sem_Type
; use Sem_Type
;
56 with Sem_Util
; use Sem_Util
;
57 with Sem_Warn
; use Sem_Warn
;
58 with Snames
; use Snames
;
59 with Stand
; use Stand
;
60 with Sinfo
; use Sinfo
;
61 with Targparm
; use Targparm
;
62 with Tbuild
; use Tbuild
;
63 with Uintp
; use Uintp
;
65 package body Sem_Ch5
is
67 Current_LHS
: Node_Id
:= Empty
;
68 -- Holds the left-hand side of the assignment statement being analyzed.
69 -- Used to determine the type of a target_name appearing on the RHS, for
70 -- AI12-0125 and the use of '@' as an abbreviation for the LHS.
72 Unblocked_Exit_Count
: Nat
:= 0;
73 -- This variable is used when processing if statements, case statements,
74 -- and block statements. It counts the number of exit points that are not
75 -- blocked by unconditional transfer instructions: for IF and CASE, these
76 -- are the branches of the conditional; for a block, they are the statement
77 -- sequence of the block, and the statement sequences of any exception
78 -- handlers that are part of the block. When processing is complete, if
79 -- this count is zero, it means that control cannot fall through the IF,
80 -- CASE or block statement. This is used for the generation of warning
81 -- messages. This variable is recursively saved on entry to processing the
82 -- construct, and restored on exit.
84 procedure Preanalyze_Range
(R_Copy
: Node_Id
);
85 -- Determine expected type of range or domain of iteration of Ada 2012
86 -- loop by analyzing separate copy. Do the analysis and resolution of the
87 -- copy of the bound(s) with expansion disabled, to prevent the generation
88 -- of finalization actions. This prevents memory leaks when the bounds
89 -- contain calls to functions returning controlled arrays or when the
90 -- domain of iteration is a container.
92 ------------------------
93 -- Analyze_Assignment --
94 ------------------------
96 -- WARNING: This routine manages Ghost regions. Return statements must be
97 -- replaced by gotos which jump to the end of the routine and restore the
100 procedure Analyze_Assignment
(N
: Node_Id
) is
101 Lhs
: constant Node_Id
:= Name
(N
);
102 Rhs
: constant Node_Id
:= Expression
(N
);
107 procedure Diagnose_Non_Variable_Lhs
(N
: Node_Id
);
108 -- N is the node for the left hand side of an assignment, and it is not
109 -- a variable. This routine issues an appropriate diagnostic.
112 -- This is called to kill current value settings of a simple variable
113 -- on the left hand side. We call it if we find any error in analyzing
114 -- the assignment, and at the end of processing before setting any new
115 -- current values in place.
117 procedure Set_Assignment_Type
119 Opnd_Type
: in out Entity_Id
);
120 -- Opnd is either the Lhs or Rhs of the assignment, and Opnd_Type is the
121 -- nominal subtype. This procedure is used to deal with cases where the
122 -- nominal subtype must be replaced by the actual subtype.
124 -------------------------------
125 -- Diagnose_Non_Variable_Lhs --
126 -------------------------------
128 procedure Diagnose_Non_Variable_Lhs
(N
: Node_Id
) is
130 -- Not worth posting another error if left hand side already flagged
131 -- as being illegal in some respect.
133 if Error_Posted
(N
) then
136 -- Some special bad cases of entity names
138 elsif Is_Entity_Name
(N
) then
140 Ent
: constant Entity_Id
:= Entity
(N
);
143 if Ekind
(Ent
) = E_In_Parameter
then
145 ("assignment to IN mode parameter not allowed", N
);
148 -- Renamings of protected private components are turned into
149 -- constants when compiling a protected function. In the case
150 -- of single protected types, the private component appears
153 elsif (Is_Prival
(Ent
)
155 (Ekind
(Current_Scope
) = E_Function
156 or else Ekind
(Enclosing_Dynamic_Scope
157 (Current_Scope
)) = E_Function
))
159 (Ekind
(Ent
) = E_Component
160 and then Is_Protected_Type
(Scope
(Ent
)))
163 ("protected function cannot modify protected object", N
);
166 elsif Ekind
(Ent
) = E_Loop_Parameter
then
167 Error_Msg_N
("assignment to loop parameter not allowed", N
);
172 -- For indexed components, test prefix if it is in array. We do not
173 -- want to recurse for cases where the prefix is a pointer, since we
174 -- may get a message confusing the pointer and what it references.
176 elsif Nkind
(N
) = N_Indexed_Component
177 and then Is_Array_Type
(Etype
(Prefix
(N
)))
179 Diagnose_Non_Variable_Lhs
(Prefix
(N
));
182 -- Another special case for assignment to discriminant
184 elsif Nkind
(N
) = N_Selected_Component
then
185 if Present
(Entity
(Selector_Name
(N
)))
186 and then Ekind
(Entity
(Selector_Name
(N
))) = E_Discriminant
188 Error_Msg_N
("assignment to discriminant not allowed", N
);
191 -- For selection from record, diagnose prefix, but note that again
192 -- we only do this for a record, not e.g. for a pointer.
194 elsif Is_Record_Type
(Etype
(Prefix
(N
))) then
195 Diagnose_Non_Variable_Lhs
(Prefix
(N
));
200 -- If we fall through, we have no special message to issue
202 Error_Msg_N
("left hand side of assignment must be a variable", N
);
203 end Diagnose_Non_Variable_Lhs
;
209 procedure Kill_Lhs
is
211 if Is_Entity_Name
(Lhs
) then
213 Ent
: constant Entity_Id
:= Entity
(Lhs
);
215 if Present
(Ent
) then
216 Kill_Current_Values
(Ent
);
222 -------------------------
223 -- Set_Assignment_Type --
224 -------------------------
226 procedure Set_Assignment_Type
228 Opnd_Type
: in out Entity_Id
)
231 Require_Entity
(Opnd
);
233 -- If the assignment operand is an in-out or out parameter, then we
234 -- get the actual subtype (needed for the unconstrained case). If the
235 -- operand is the actual in an entry declaration, then within the
236 -- accept statement it is replaced with a local renaming, which may
237 -- also have an actual subtype.
239 if Is_Entity_Name
(Opnd
)
240 and then (Ekind
(Entity
(Opnd
)) = E_Out_Parameter
241 or else Ekind_In
(Entity
(Opnd
),
243 E_Generic_In_Out_Parameter
)
245 (Ekind
(Entity
(Opnd
)) = E_Variable
246 and then Nkind
(Parent
(Entity
(Opnd
))) =
247 N_Object_Renaming_Declaration
248 and then Nkind
(Parent
(Parent
(Entity
(Opnd
)))) =
251 Opnd_Type
:= Get_Actual_Subtype
(Opnd
);
253 -- If assignment operand is a component reference, then we get the
254 -- actual subtype of the component for the unconstrained case.
256 elsif Nkind_In
(Opnd
, N_Selected_Component
, N_Explicit_Dereference
)
257 and then not Is_Unchecked_Union
(Opnd_Type
)
259 Decl
:= Build_Actual_Subtype_Of_Component
(Opnd_Type
, Opnd
);
261 if Present
(Decl
) then
262 Insert_Action
(N
, Decl
);
263 Mark_Rewrite_Insertion
(Decl
);
265 Opnd_Type
:= Defining_Identifier
(Decl
);
266 Set_Etype
(Opnd
, Opnd_Type
);
267 Freeze_Itype
(Opnd_Type
, N
);
269 elsif Is_Constrained
(Etype
(Opnd
)) then
270 Opnd_Type
:= Etype
(Opnd
);
273 -- For slice, use the constrained subtype created for the slice
275 elsif Nkind
(Opnd
) = N_Slice
then
276 Opnd_Type
:= Etype
(Opnd
);
278 end Set_Assignment_Type
;
282 Mode
: Ghost_Mode_Type
;
284 -- Start of processing for Analyze_Assignment
287 -- Save LHS for use in target names (AI12-125)
291 Mark_Coextensions
(N
, Rhs
);
293 -- Analyze the target of the assignment first in case the expression
294 -- contains references to Ghost entities. The checks that verify the
295 -- proper use of a Ghost entity need to know the enclosing context.
299 -- An assignment statement is Ghost when the left hand side denotes a
300 -- Ghost entity. Set the mode now to ensure that any nodes generated
301 -- during analysis and expansion are properly marked as Ghost.
303 Mark_And_Set_Ghost_Assignment
(N
, Mode
);
306 -- Ensure that we never do an assignment on a variable marked as
307 -- as Safe_To_Reevaluate.
309 pragma Assert
(not Is_Entity_Name
(Lhs
)
310 or else Ekind
(Entity
(Lhs
)) /= E_Variable
311 or else not Is_Safe_To_Reevaluate
(Entity
(Lhs
)));
313 -- Start type analysis for assignment
317 -- In the most general case, both Lhs and Rhs can be overloaded, and we
318 -- must compute the intersection of the possible types on each side.
320 if Is_Overloaded
(Lhs
) then
327 Get_First_Interp
(Lhs
, I
, It
);
329 while Present
(It
.Typ
) loop
331 -- An indexed component with generalized indexing is always
332 -- overloaded with the corresponding dereference. Discard the
333 -- interpretation that yields a reference type, which is not
336 if Nkind
(Lhs
) = N_Indexed_Component
337 and then Present
(Generalized_Indexing
(Lhs
))
338 and then Has_Implicit_Dereference
(It
.Typ
)
342 -- This may be a call to a parameterless function through an
343 -- implicit dereference, so discard interpretation as well.
345 elsif Is_Entity_Name
(Lhs
)
346 and then Has_Implicit_Dereference
(It
.Typ
)
350 elsif Has_Compatible_Type
(Rhs
, It
.Typ
) then
351 if T1
/= Any_Type
then
353 -- An explicit dereference is overloaded if the prefix
354 -- is. Try to remove the ambiguity on the prefix, the
355 -- error will be posted there if the ambiguity is real.
357 if Nkind
(Lhs
) = N_Explicit_Dereference
then
360 PI1
: Interp_Index
:= 0;
366 Get_First_Interp
(Prefix
(Lhs
), PI
, PIt
);
368 while Present
(PIt
.Typ
) loop
369 if Is_Access_Type
(PIt
.Typ
)
370 and then Has_Compatible_Type
371 (Rhs
, Designated_Type
(PIt
.Typ
))
375 Disambiguate
(Prefix
(Lhs
),
378 if PIt
= No_Interp
then
380 ("ambiguous left-hand side in "
381 & "assignment", Lhs
);
384 Resolve
(Prefix
(Lhs
), PIt
.Typ
);
394 Get_Next_Interp
(PI
, PIt
);
400 ("ambiguous left-hand side in assignment", Lhs
);
408 Get_Next_Interp
(I
, It
);
412 if T1
= Any_Type
then
414 ("no valid types for left-hand side for assignment", Lhs
);
420 -- The resulting assignment type is T1, so now we will resolve the left
421 -- hand side of the assignment using this determined type.
425 -- Cases where Lhs is not a variable
427 -- Cases where Lhs is not a variable. In an instance or an inlined body
428 -- no need for further check because assignment was legal in template.
430 if In_Inlined_Body
then
433 elsif not Is_Variable
(Lhs
) then
435 -- Ada 2005 (AI-327): Check assignment to the attribute Priority of a
443 if Ada_Version
>= Ada_2005
then
445 -- Handle chains of renamings
448 while Nkind
(Ent
) in N_Has_Entity
449 and then Present
(Entity
(Ent
))
450 and then Present
(Renamed_Object
(Entity
(Ent
)))
452 Ent
:= Renamed_Object
(Entity
(Ent
));
455 if (Nkind
(Ent
) = N_Attribute_Reference
456 and then Attribute_Name
(Ent
) = Name_Priority
)
458 -- Renamings of the attribute Priority applied to protected
459 -- objects have been previously expanded into calls to the
460 -- Get_Ceiling run-time subprogram.
462 or else Is_Expanded_Priority_Attribute
(Ent
)
464 -- The enclosing subprogram cannot be a protected function
467 while not (Is_Subprogram
(S
)
468 and then Convention
(S
) = Convention_Protected
)
469 and then S
/= Standard_Standard
474 if Ekind
(S
) = E_Function
475 and then Convention
(S
) = Convention_Protected
478 ("protected function cannot modify protected object",
482 -- Changes of the ceiling priority of the protected object
483 -- are only effective if the Ceiling_Locking policy is in
484 -- effect (AARM D.5.2 (5/2)).
486 if Locking_Policy
/= 'C' then
488 ("assignment to the attribute PRIORITY has no effect??",
491 ("\since no Locking_Policy has been specified??", Lhs
);
499 Diagnose_Non_Variable_Lhs
(Lhs
);
502 -- Error of assigning to limited type. We do however allow this in
503 -- certain cases where the front end generates the assignments.
505 elsif Is_Limited_Type
(T1
)
506 and then not Assignment_OK
(Lhs
)
507 and then not Assignment_OK
(Original_Node
(Lhs
))
509 -- CPP constructors can only be called in declarations
511 if Is_CPP_Constructor_Call
(Rhs
) then
512 Error_Msg_N
("invalid use of 'C'P'P constructor", Rhs
);
515 ("left hand of assignment must not be limited type", Lhs
);
516 Explain_Limited_Type
(T1
, Lhs
);
521 -- A class-wide type may be a limited view. This illegal case is not
522 -- caught by previous checks.
524 elsif Ekind
(T1
) = E_Class_Wide_Type
and then From_Limited_With
(T1
) then
525 Error_Msg_NE
("invalid use of limited view of&", Lhs
, T1
);
528 -- Enforce RM 3.9.3 (8): the target of an assignment operation cannot be
529 -- abstract. This is only checked when the assignment Comes_From_Source,
530 -- because in some cases the expander generates such assignments (such
531 -- in the _assign operation for an abstract type).
533 elsif Is_Abstract_Type
(T1
) and then Comes_From_Source
(N
) then
535 ("target of assignment operation must not be abstract", Lhs
);
538 -- Resolution may have updated the subtype, in case the left-hand side
539 -- is a private protected component. Use the correct subtype to avoid
540 -- scoping issues in the back-end.
544 -- Ada 2005 (AI-50217, AI-326): Check wrong dereference of incomplete
545 -- type. For example:
549 -- type Acc is access P.T;
552 -- with Pkg; use Acc;
553 -- procedure Example is
556 -- A.all := B.all; -- ERROR
559 if Nkind
(Lhs
) = N_Explicit_Dereference
560 and then Ekind
(T1
) = E_Incomplete_Type
562 Error_Msg_N
("invalid use of incomplete type", Lhs
);
567 -- Now we can complete the resolution of the right hand side
569 Set_Assignment_Type
(Lhs
, T1
);
573 -- If the right-hand side contains target names, expansion has been
574 -- disabled to prevent expansion that might move target names out of
575 -- the context of the assignment statement. Restore the expander mode
576 -- now so that assignment statement can be properly expanded.
578 if Nkind
(N
) = N_Assignment_Statement
and then Has_Target_Names
(N
) then
579 Expander_Mode_Restore
;
582 -- This is the point at which we check for an unset reference
584 Check_Unset_Reference
(Rhs
);
585 Check_Unprotected_Access
(Lhs
, Rhs
);
587 -- Remaining steps are skipped if Rhs was syntactically in error
596 if not Covers
(T1
, T2
) then
597 Wrong_Type
(Rhs
, Etype
(Lhs
));
602 -- Ada 2005 (AI-326): In case of explicit dereference of incomplete
603 -- types, use the non-limited view if available
605 if Nkind
(Rhs
) = N_Explicit_Dereference
606 and then Is_Tagged_Type
(T2
)
607 and then Has_Non_Limited_View
(T2
)
609 T2
:= Non_Limited_View
(T2
);
612 Set_Assignment_Type
(Rhs
, T2
);
614 if Total_Errors_Detected
/= 0 then
624 if T1
= Any_Type
or else T2
= Any_Type
then
629 -- If the rhs is class-wide or dynamically tagged, then require the lhs
630 -- to be class-wide. The case where the rhs is a dynamically tagged call
631 -- to a dispatching operation with a controlling access result is
632 -- excluded from this check, since the target has an access type (and
633 -- no tag propagation occurs in that case).
635 if (Is_Class_Wide_Type
(T2
)
636 or else (Is_Dynamically_Tagged
(Rhs
)
637 and then not Is_Access_Type
(T1
)))
638 and then not Is_Class_Wide_Type
(T1
)
640 Error_Msg_N
("dynamically tagged expression not allowed!", Rhs
);
642 elsif Is_Class_Wide_Type
(T1
)
643 and then not Is_Class_Wide_Type
(T2
)
644 and then not Is_Tag_Indeterminate
(Rhs
)
645 and then not Is_Dynamically_Tagged
(Rhs
)
647 Error_Msg_N
("dynamically tagged expression required!", Rhs
);
650 -- Propagate the tag from a class-wide target to the rhs when the rhs
651 -- is a tag-indeterminate call.
653 if Is_Tag_Indeterminate
(Rhs
) then
654 if Is_Class_Wide_Type
(T1
) then
655 Propagate_Tag
(Lhs
, Rhs
);
657 elsif Nkind
(Rhs
) = N_Function_Call
658 and then Is_Entity_Name
(Name
(Rhs
))
659 and then Is_Abstract_Subprogram
(Entity
(Name
(Rhs
)))
662 ("call to abstract function must be dispatching", Name
(Rhs
));
664 elsif Nkind
(Rhs
) = N_Qualified_Expression
665 and then Nkind
(Expression
(Rhs
)) = N_Function_Call
666 and then Is_Entity_Name
(Name
(Expression
(Rhs
)))
668 Is_Abstract_Subprogram
(Entity
(Name
(Expression
(Rhs
))))
671 ("call to abstract function must be dispatching",
672 Name
(Expression
(Rhs
)));
676 -- Ada 2005 (AI-385): When the lhs type is an anonymous access type,
677 -- apply an implicit conversion of the rhs to that type to force
678 -- appropriate static and run-time accessibility checks. This applies
679 -- as well to anonymous access-to-subprogram types that are component
680 -- subtypes or formal parameters.
682 if Ada_Version
>= Ada_2005
and then Is_Access_Type
(T1
) then
683 if Is_Local_Anonymous_Access
(T1
)
684 or else Ekind
(T2
) = E_Anonymous_Access_Subprogram_Type
686 -- Handle assignment to an Ada 2012 stand-alone object
687 -- of an anonymous access type.
689 or else (Ekind
(T1
) = E_Anonymous_Access_Type
690 and then Nkind
(Associated_Node_For_Itype
(T1
)) =
691 N_Object_Declaration
)
694 Rewrite
(Rhs
, Convert_To
(T1
, Relocate_Node
(Rhs
)));
695 Analyze_And_Resolve
(Rhs
, T1
);
699 -- Ada 2005 (AI-231): Assignment to not null variable
701 if Ada_Version
>= Ada_2005
702 and then Can_Never_Be_Null
(T1
)
703 and then not Assignment_OK
(Lhs
)
705 -- Case where we know the right hand side is null
707 if Known_Null
(Rhs
) then
708 Apply_Compile_Time_Constraint_Error
711 "(Ada 2005) null not allowed in null-excluding objects??",
712 Reason
=> CE_Null_Not_Allowed
);
714 -- We still mark this as a possible modification, that's necessary
715 -- to reset Is_True_Constant, and desirable for xref purposes.
717 Note_Possible_Modification
(Lhs
, Sure
=> True);
720 -- If we know the right hand side is non-null, then we convert to the
721 -- target type, since we don't need a run time check in that case.
723 elsif not Can_Never_Be_Null
(T2
) then
724 Rewrite
(Rhs
, Convert_To
(T1
, Relocate_Node
(Rhs
)));
725 Analyze_And_Resolve
(Rhs
, T1
);
729 if Is_Scalar_Type
(T1
) then
730 Apply_Scalar_Range_Check
(Rhs
, Etype
(Lhs
));
732 -- For array types, verify that lengths match. If the right hand side
733 -- is a function call that has been inlined, the assignment has been
734 -- rewritten as a block, and the constraint check will be applied to the
735 -- assignment within the block.
737 elsif Is_Array_Type
(T1
)
738 and then (Nkind
(Rhs
) /= N_Type_Conversion
739 or else Is_Constrained
(Etype
(Rhs
)))
740 and then (Nkind
(Rhs
) /= N_Function_Call
741 or else Nkind
(N
) /= N_Block_Statement
)
743 -- Assignment verifies that the length of the Lsh and Rhs are equal,
744 -- but of course the indexes do not have to match. If the right-hand
745 -- side is a type conversion to an unconstrained type, a length check
746 -- is performed on the expression itself during expansion. In rare
747 -- cases, the redundant length check is computed on an index type
748 -- with a different representation, triggering incorrect code in the
751 Apply_Length_Check
(Rhs
, Etype
(Lhs
));
754 -- Discriminant checks are applied in the course of expansion
759 -- Note: modifications of the Lhs may only be recorded after
760 -- checks have been applied.
762 Note_Possible_Modification
(Lhs
, Sure
=> True);
764 -- ??? a real accessibility check is needed when ???
766 -- Post warning for redundant assignment or variable to itself
768 if Warn_On_Redundant_Constructs
770 -- We only warn for source constructs
772 and then Comes_From_Source
(N
)
774 -- Where the object is the same on both sides
776 and then Same_Object
(Lhs
, Original_Node
(Rhs
))
778 -- But exclude the case where the right side was an operation that
779 -- got rewritten (e.g. JUNK + K, where K was known to be zero). We
780 -- don't want to warn in such a case, since it is reasonable to write
781 -- such expressions especially when K is defined symbolically in some
784 and then Nkind
(Original_Node
(Rhs
)) not in N_Op
786 if Nkind
(Lhs
) in N_Has_Entity
then
787 Error_Msg_NE
-- CODEFIX
788 ("?r?useless assignment of & to itself!", N
, Entity
(Lhs
));
790 Error_Msg_N
-- CODEFIX
791 ("?r?useless assignment of object to itself!", N
);
795 -- Check for non-allowed composite assignment
797 if not Support_Composite_Assign_On_Target
798 and then (Is_Array_Type
(T1
) or else Is_Record_Type
(T1
))
799 and then (not Has_Size_Clause
(T1
) or else Esize
(T1
) > 64)
801 Error_Msg_CRT
("composite assignment", N
);
804 -- Check elaboration warning for left side if not in elab code
806 if not In_Subprogram_Or_Concurrent_Unit
then
807 Check_Elab_Assign
(Lhs
);
810 -- Set Referenced_As_LHS if appropriate. We only set this flag if the
811 -- assignment is a source assignment in the extended main source unit.
812 -- We are not interested in any reference information outside this
813 -- context, or in compiler generated assignment statements.
815 if Comes_From_Source
(N
)
816 and then In_Extended_Main_Source_Unit
(Lhs
)
818 Set_Referenced_Modified
(Lhs
, Out_Param
=> False);
821 -- RM 7.3.2 (12/3): An assignment to a view conversion (from a type
822 -- to one of its ancestors) requires an invariant check. Apply check
823 -- only if expression comes from source, otherwise it will be applied
824 -- when value is assigned to source entity.
826 if Nkind
(Lhs
) = N_Type_Conversion
827 and then Has_Invariants
(Etype
(Expression
(Lhs
)))
828 and then Comes_From_Source
(Expression
(Lhs
))
830 Insert_After
(N
, Make_Invariant_Call
(Expression
(Lhs
)));
833 -- Final step. If left side is an entity, then we may be able to reset
834 -- the current tracked values to new safe values. We only have something
835 -- to do if the left side is an entity name, and expansion has not
836 -- modified the node into something other than an assignment, and of
837 -- course we only capture values if it is safe to do so.
839 if Is_Entity_Name
(Lhs
)
840 and then Nkind
(N
) = N_Assignment_Statement
843 Ent
: constant Entity_Id
:= Entity
(Lhs
);
846 if Safe_To_Capture_Value
(N
, Ent
) then
848 -- If simple variable on left side, warn if this assignment
849 -- blots out another one (rendering it useless). We only do
850 -- this for source assignments, otherwise we can generate bogus
851 -- warnings when an assignment is rewritten as another
852 -- assignment, and gets tied up with itself.
854 -- There may have been a previous reference to a component of
855 -- the variable, which in general removes the Last_Assignment
856 -- field of the variable to indicate a relevant use of the
857 -- previous assignment. However, if the assignment is to a
858 -- subcomponent the reference may not have registered, because
859 -- it is not possible to determine whether the context is an
860 -- assignment. In those cases we generate a Deferred_Reference,
861 -- to be used at the end of compilation to generate the right
862 -- kind of reference, and we suppress a potential warning for
863 -- a useless assignment, which might be premature. This may
864 -- lose a warning in rare cases, but seems preferable to a
865 -- misleading warning.
867 if Warn_On_Modified_Unread
868 and then Is_Assignable
(Ent
)
869 and then Comes_From_Source
(N
)
870 and then In_Extended_Main_Source_Unit
(Ent
)
871 and then not Has_Deferred_Reference
(Ent
)
873 Warn_On_Useless_Assignment
(Ent
, N
);
876 -- If we are assigning an access type and the left side is an
877 -- entity, then make sure that the Is_Known_[Non_]Null flags
878 -- properly reflect the state of the entity after assignment.
880 if Is_Access_Type
(T1
) then
881 if Known_Non_Null
(Rhs
) then
882 Set_Is_Known_Non_Null
(Ent
, True);
884 elsif Known_Null
(Rhs
)
885 and then not Can_Never_Be_Null
(Ent
)
887 Set_Is_Known_Null
(Ent
, True);
890 Set_Is_Known_Null
(Ent
, False);
892 if not Can_Never_Be_Null
(Ent
) then
893 Set_Is_Known_Non_Null
(Ent
, False);
897 -- For discrete types, we may be able to set the current value
898 -- if the value is known at compile time.
900 elsif Is_Discrete_Type
(T1
)
901 and then Compile_Time_Known_Value
(Rhs
)
903 Set_Current_Value
(Ent
, Rhs
);
905 Set_Current_Value
(Ent
, Empty
);
908 -- If not safe to capture values, kill them
916 -- If assigning to an object in whole or in part, note location of
917 -- assignment in case no one references value. We only do this for
918 -- source assignments, otherwise we can generate bogus warnings when an
919 -- assignment is rewritten as another assignment, and gets tied up with
923 Ent
: constant Entity_Id
:= Get_Enclosing_Object
(Lhs
);
926 and then Safe_To_Capture_Value
(N
, Ent
)
927 and then Nkind
(N
) = N_Assignment_Statement
928 and then Warn_On_Modified_Unread
929 and then Is_Assignable
(Ent
)
930 and then Comes_From_Source
(N
)
931 and then In_Extended_Main_Source_Unit
(Ent
)
933 Set_Last_Assignment
(Ent
, Lhs
);
937 Analyze_Dimension
(N
);
940 Current_LHS
:= Empty
;
941 Restore_Ghost_Mode
(Mode
);
942 end Analyze_Assignment
;
944 -----------------------------
945 -- Analyze_Block_Statement --
946 -----------------------------
948 procedure Analyze_Block_Statement
(N
: Node_Id
) is
949 procedure Install_Return_Entities
(Scop
: Entity_Id
);
950 -- Install all entities of return statement scope Scop in the visibility
951 -- chain except for the return object since its entity is reused in a
954 -----------------------------
955 -- Install_Return_Entities --
956 -----------------------------
958 procedure Install_Return_Entities
(Scop
: Entity_Id
) is
962 Id
:= First_Entity
(Scop
);
963 while Present
(Id
) loop
965 -- Do not install the return object
967 if not Ekind_In
(Id
, E_Constant
, E_Variable
)
968 or else not Is_Return_Object
(Id
)
975 end Install_Return_Entities
;
977 -- Local constants and variables
979 Decls
: constant List_Id
:= Declarations
(N
);
980 Id
: constant Node_Id
:= Identifier
(N
);
981 HSS
: constant Node_Id
:= Handled_Statement_Sequence
(N
);
983 Is_BIP_Return_Statement
: Boolean;
985 -- Start of processing for Analyze_Block_Statement
988 -- In SPARK mode, we reject block statements. Note that the case of
989 -- block statements generated by the expander is fine.
991 if Nkind
(Original_Node
(N
)) = N_Block_Statement
then
992 Check_SPARK_05_Restriction
("block statement is not allowed", N
);
995 -- If no handled statement sequence is present, things are really messed
996 -- up, and we just return immediately (defence against previous errors).
999 Check_Error_Detected
;
1003 -- Detect whether the block is actually a rewritten return statement of
1004 -- a build-in-place function.
1006 Is_BIP_Return_Statement
:=
1008 and then Present
(Entity
(Id
))
1009 and then Ekind
(Entity
(Id
)) = E_Return_Statement
1010 and then Is_Build_In_Place_Function
1011 (Return_Applies_To
(Entity
(Id
)));
1013 -- Normal processing with HSS present
1016 EH
: constant List_Id
:= Exception_Handlers
(HSS
);
1017 Ent
: Entity_Id
:= Empty
;
1020 Save_Unblocked_Exit_Count
: constant Nat
:= Unblocked_Exit_Count
;
1021 -- Recursively save value of this global, will be restored on exit
1024 -- Initialize unblocked exit count for statements of begin block
1025 -- plus one for each exception handler that is present.
1027 Unblocked_Exit_Count
:= 1;
1029 if Present
(EH
) then
1030 Unblocked_Exit_Count
:= Unblocked_Exit_Count
+ List_Length
(EH
);
1033 -- If a label is present analyze it and mark it as referenced
1035 if Present
(Id
) then
1039 -- An error defense. If we have an identifier, but no entity, then
1040 -- something is wrong. If previous errors, then just remove the
1041 -- identifier and continue, otherwise raise an exception.
1044 Check_Error_Detected
;
1045 Set_Identifier
(N
, Empty
);
1048 Set_Ekind
(Ent
, E_Block
);
1049 Generate_Reference
(Ent
, N
, ' ');
1050 Generate_Definition
(Ent
);
1052 if Nkind
(Parent
(Ent
)) = N_Implicit_Label_Declaration
then
1053 Set_Label_Construct
(Parent
(Ent
), N
);
1058 -- If no entity set, create a label entity
1061 Ent
:= New_Internal_Entity
(E_Block
, Current_Scope
, Sloc
(N
), 'B');
1062 Set_Identifier
(N
, New_Occurrence_Of
(Ent
, Sloc
(N
)));
1063 Set_Parent
(Ent
, N
);
1066 Set_Etype
(Ent
, Standard_Void_Type
);
1067 Set_Block_Node
(Ent
, Identifier
(N
));
1070 -- The block served as an extended return statement. Ensure that any
1071 -- entities created during the analysis and expansion of the return
1072 -- object declaration are once again visible.
1074 if Is_BIP_Return_Statement
then
1075 Install_Return_Entities
(Ent
);
1078 if Present
(Decls
) then
1079 Analyze_Declarations
(Decls
);
1081 Inspect_Deferred_Constant_Completion
(Decls
);
1085 Process_End_Label
(HSS
, 'e', Ent
);
1087 -- If exception handlers are present, then we indicate that enclosing
1088 -- scopes contain a block with handlers. We only need to mark non-
1091 if Present
(EH
) then
1094 Set_Has_Nested_Block_With_Handler
(S
);
1095 exit when Is_Overloadable
(S
)
1096 or else Ekind
(S
) = E_Package
1097 or else Is_Generic_Unit
(S
);
1102 Check_References
(Ent
);
1105 if Unblocked_Exit_Count
= 0 then
1106 Unblocked_Exit_Count
:= Save_Unblocked_Exit_Count
;
1107 Check_Unreachable_Code
(N
);
1109 Unblocked_Exit_Count
:= Save_Unblocked_Exit_Count
;
1112 end Analyze_Block_Statement
;
1114 --------------------------------
1115 -- Analyze_Compound_Statement --
1116 --------------------------------
1118 procedure Analyze_Compound_Statement
(N
: Node_Id
) is
1120 Analyze_List
(Actions
(N
));
1121 end Analyze_Compound_Statement
;
1123 ----------------------------
1124 -- Analyze_Case_Statement --
1125 ----------------------------
1127 procedure Analyze_Case_Statement
(N
: Node_Id
) is
1129 Exp_Type
: Entity_Id
;
1130 Exp_Btype
: Entity_Id
;
1133 Others_Present
: Boolean;
1134 -- Indicates if Others was present
1136 pragma Warnings
(Off
, Last_Choice
);
1137 -- Don't care about assigned value
1139 Statements_Analyzed
: Boolean := False;
1140 -- Set True if at least some statement sequences get analyzed. If False
1141 -- on exit, means we had a serious error that prevented full analysis of
1142 -- the case statement, and as a result it is not a good idea to output
1143 -- warning messages about unreachable code.
1145 Save_Unblocked_Exit_Count
: constant Nat
:= Unblocked_Exit_Count
;
1146 -- Recursively save value of this global, will be restored on exit
1148 procedure Non_Static_Choice_Error
(Choice
: Node_Id
);
1149 -- Error routine invoked by the generic instantiation below when the
1150 -- case statement has a non static choice.
1152 procedure Process_Statements
(Alternative
: Node_Id
);
1153 -- Analyzes the statements associated with a case alternative. Needed
1154 -- by instantiation below.
1156 package Analyze_Case_Choices
is new
1157 Generic_Analyze_Choices
1158 (Process_Associated_Node
=> Process_Statements
);
1159 use Analyze_Case_Choices
;
1160 -- Instantiation of the generic choice analysis package
1162 package Check_Case_Choices
is new
1163 Generic_Check_Choices
1164 (Process_Empty_Choice
=> No_OP
,
1165 Process_Non_Static_Choice
=> Non_Static_Choice_Error
,
1166 Process_Associated_Node
=> No_OP
);
1167 use Check_Case_Choices
;
1168 -- Instantiation of the generic choice processing package
1170 -----------------------------
1171 -- Non_Static_Choice_Error --
1172 -----------------------------
1174 procedure Non_Static_Choice_Error
(Choice
: Node_Id
) is
1176 Flag_Non_Static_Expr
1177 ("choice given in case statement is not static!", Choice
);
1178 end Non_Static_Choice_Error
;
1180 ------------------------
1181 -- Process_Statements --
1182 ------------------------
1184 procedure Process_Statements
(Alternative
: Node_Id
) is
1185 Choices
: constant List_Id
:= Discrete_Choices
(Alternative
);
1189 Unblocked_Exit_Count
:= Unblocked_Exit_Count
+ 1;
1190 Statements_Analyzed
:= True;
1192 -- An interesting optimization. If the case statement expression
1193 -- is a simple entity, then we can set the current value within an
1194 -- alternative if the alternative has one possible value.
1198 -- when 2 | 3 => beta
1199 -- when others => gamma
1201 -- Here we know that N is initially 1 within alpha, but for beta and
1202 -- gamma, we do not know anything more about the initial value.
1204 if Is_Entity_Name
(Exp
) then
1205 Ent
:= Entity
(Exp
);
1207 if Ekind_In
(Ent
, E_Variable
,
1211 if List_Length
(Choices
) = 1
1212 and then Nkind
(First
(Choices
)) in N_Subexpr
1213 and then Compile_Time_Known_Value
(First
(Choices
))
1215 Set_Current_Value
(Entity
(Exp
), First
(Choices
));
1218 Analyze_Statements
(Statements
(Alternative
));
1220 -- After analyzing the case, set the current value to empty
1221 -- since we won't know what it is for the next alternative
1222 -- (unless reset by this same circuit), or after the case.
1224 Set_Current_Value
(Entity
(Exp
), Empty
);
1229 -- Case where expression is not an entity name of a variable
1231 Analyze_Statements
(Statements
(Alternative
));
1232 end Process_Statements
;
1234 -- Start of processing for Analyze_Case_Statement
1237 Unblocked_Exit_Count
:= 0;
1238 Exp
:= Expression
(N
);
1241 -- The expression must be of any discrete type. In rare cases, the
1242 -- expander constructs a case statement whose expression has a private
1243 -- type whose full view is discrete. This can happen when generating
1244 -- a stream operation for a variant type after the type is frozen,
1245 -- when the partial of view of the type of the discriminant is private.
1246 -- In that case, use the full view to analyze case alternatives.
1248 if not Is_Overloaded
(Exp
)
1249 and then not Comes_From_Source
(N
)
1250 and then Is_Private_Type
(Etype
(Exp
))
1251 and then Present
(Full_View
(Etype
(Exp
)))
1252 and then Is_Discrete_Type
(Full_View
(Etype
(Exp
)))
1254 Resolve
(Exp
, Etype
(Exp
));
1255 Exp_Type
:= Full_View
(Etype
(Exp
));
1258 Analyze_And_Resolve
(Exp
, Any_Discrete
);
1259 Exp_Type
:= Etype
(Exp
);
1262 Check_Unset_Reference
(Exp
);
1263 Exp_Btype
:= Base_Type
(Exp_Type
);
1265 -- The expression must be of a discrete type which must be determinable
1266 -- independently of the context in which the expression occurs, but
1267 -- using the fact that the expression must be of a discrete type.
1268 -- Moreover, the type this expression must not be a character literal
1269 -- (which is always ambiguous) or, for Ada-83, a generic formal type.
1271 -- If error already reported by Resolve, nothing more to do
1273 if Exp_Btype
= Any_Discrete
or else Exp_Btype
= Any_Type
then
1276 elsif Exp_Btype
= Any_Character
then
1278 ("character literal as case expression is ambiguous", Exp
);
1281 elsif Ada_Version
= Ada_83
1282 and then (Is_Generic_Type
(Exp_Btype
)
1283 or else Is_Generic_Type
(Root_Type
(Exp_Btype
)))
1286 ("(Ada 83) case expression cannot be of a generic type", Exp
);
1290 -- If the case expression is a formal object of mode in out, then treat
1291 -- it as having a nonstatic subtype by forcing use of the base type
1292 -- (which has to get passed to Check_Case_Choices below). Also use base
1293 -- type when the case expression is parenthesized.
1295 if Paren_Count
(Exp
) > 0
1296 or else (Is_Entity_Name
(Exp
)
1297 and then Ekind
(Entity
(Exp
)) = E_Generic_In_Out_Parameter
)
1299 Exp_Type
:= Exp_Btype
;
1302 -- Call instantiated procedures to analyzwe and check discrete choices
1304 Analyze_Choices
(Alternatives
(N
), Exp_Type
);
1305 Check_Choices
(N
, Alternatives
(N
), Exp_Type
, Others_Present
);
1307 -- Case statement with single OTHERS alternative not allowed in SPARK
1309 if Others_Present
and then List_Length
(Alternatives
(N
)) = 1 then
1310 Check_SPARK_05_Restriction
1311 ("OTHERS as unique case alternative is not allowed", N
);
1314 if Exp_Type
= Universal_Integer
and then not Others_Present
then
1315 Error_Msg_N
("case on universal integer requires OTHERS choice", Exp
);
1318 -- If all our exits were blocked by unconditional transfers of control,
1319 -- then the entire CASE statement acts as an unconditional transfer of
1320 -- control, so treat it like one, and check unreachable code. Skip this
1321 -- test if we had serious errors preventing any statement analysis.
1323 if Unblocked_Exit_Count
= 0 and then Statements_Analyzed
then
1324 Unblocked_Exit_Count
:= Save_Unblocked_Exit_Count
;
1325 Check_Unreachable_Code
(N
);
1327 Unblocked_Exit_Count
:= Save_Unblocked_Exit_Count
;
1330 -- If the expander is active it will detect the case of a statically
1331 -- determined single alternative and remove warnings for the case, but
1332 -- if we are not doing expansion, that circuit won't be active. Here we
1333 -- duplicate the effect of removing warnings in the same way, so that
1334 -- we will get the same set of warnings in -gnatc mode.
1336 if not Expander_Active
1337 and then Compile_Time_Known_Value
(Expression
(N
))
1338 and then Serious_Errors_Detected
= 0
1341 Chosen
: constant Node_Id
:= Find_Static_Alternative
(N
);
1345 Alt
:= First
(Alternatives
(N
));
1346 while Present
(Alt
) loop
1347 if Alt
/= Chosen
then
1348 Remove_Warning_Messages
(Statements
(Alt
));
1355 end Analyze_Case_Statement
;
1357 ----------------------------
1358 -- Analyze_Exit_Statement --
1359 ----------------------------
1361 -- If the exit includes a name, it must be the name of a currently open
1362 -- loop. Otherwise there must be an innermost open loop on the stack, to
1363 -- which the statement implicitly refers.
1365 -- Additionally, in SPARK mode:
1367 -- The exit can only name the closest enclosing loop;
1369 -- An exit with a when clause must be directly contained in a loop;
1371 -- An exit without a when clause must be directly contained in an
1372 -- if-statement with no elsif or else, which is itself directly contained
1373 -- in a loop. The exit must be the last statement in the if-statement.
1375 procedure Analyze_Exit_Statement
(N
: Node_Id
) is
1376 Target
: constant Node_Id
:= Name
(N
);
1377 Cond
: constant Node_Id
:= Condition
(N
);
1378 Scope_Id
: Entity_Id
;
1384 Check_Unreachable_Code
(N
);
1387 if Present
(Target
) then
1389 U_Name
:= Entity
(Target
);
1391 if not In_Open_Scopes
(U_Name
) or else Ekind
(U_Name
) /= E_Loop
then
1392 Error_Msg_N
("invalid loop name in exit statement", N
);
1396 if Has_Loop_In_Inner_Open_Scopes
(U_Name
) then
1397 Check_SPARK_05_Restriction
1398 ("exit label must name the closest enclosing loop", N
);
1401 Set_Has_Exit
(U_Name
);
1408 for J
in reverse 0 .. Scope_Stack
.Last
loop
1409 Scope_Id
:= Scope_Stack
.Table
(J
).Entity
;
1410 Kind
:= Ekind
(Scope_Id
);
1412 if Kind
= E_Loop
and then (No
(Target
) or else Scope_Id
= U_Name
) then
1413 Set_Has_Exit
(Scope_Id
);
1416 elsif Kind
= E_Block
1417 or else Kind
= E_Loop
1418 or else Kind
= E_Return_Statement
1424 ("cannot exit from program unit or accept statement", N
);
1429 -- Verify that if present the condition is a Boolean expression
1431 if Present
(Cond
) then
1432 Analyze_And_Resolve
(Cond
, Any_Boolean
);
1433 Check_Unset_Reference
(Cond
);
1436 -- In SPARK mode, verify that the exit statement respects the SPARK
1439 if Present
(Cond
) then
1440 if Nkind
(Parent
(N
)) /= N_Loop_Statement
then
1441 Check_SPARK_05_Restriction
1442 ("exit with when clause must be directly in loop", N
);
1446 if Nkind
(Parent
(N
)) /= N_If_Statement
then
1447 if Nkind
(Parent
(N
)) = N_Elsif_Part
then
1448 Check_SPARK_05_Restriction
1449 ("exit must be in IF without ELSIF", N
);
1451 Check_SPARK_05_Restriction
("exit must be directly in IF", N
);
1454 elsif Nkind
(Parent
(Parent
(N
))) /= N_Loop_Statement
then
1455 Check_SPARK_05_Restriction
1456 ("exit must be in IF directly in loop", N
);
1458 -- First test the presence of ELSE, so that an exit in an ELSE leads
1459 -- to an error mentioning the ELSE.
1461 elsif Present
(Else_Statements
(Parent
(N
))) then
1462 Check_SPARK_05_Restriction
("exit must be in IF without ELSE", N
);
1464 -- An exit in an ELSIF does not reach here, as it would have been
1465 -- detected in the case (Nkind (Parent (N)) /= N_If_Statement).
1467 elsif Present
(Elsif_Parts
(Parent
(N
))) then
1468 Check_SPARK_05_Restriction
("exit must be in IF without ELSIF", N
);
1472 -- Chain exit statement to associated loop entity
1474 Set_Next_Exit_Statement
(N
, First_Exit_Statement
(Scope_Id
));
1475 Set_First_Exit_Statement
(Scope_Id
, N
);
1477 -- Since the exit may take us out of a loop, any previous assignment
1478 -- statement is not useless, so clear last assignment indications. It
1479 -- is OK to keep other current values, since if the exit statement
1480 -- does not exit, then the current values are still valid.
1482 Kill_Current_Values
(Last_Assignment_Only
=> True);
1483 end Analyze_Exit_Statement
;
1485 ----------------------------
1486 -- Analyze_Goto_Statement --
1487 ----------------------------
1489 procedure Analyze_Goto_Statement
(N
: Node_Id
) is
1490 Label
: constant Node_Id
:= Name
(N
);
1491 Scope_Id
: Entity_Id
;
1492 Label_Scope
: Entity_Id
;
1493 Label_Ent
: Entity_Id
;
1496 Check_SPARK_05_Restriction
("goto statement is not allowed", N
);
1498 -- Actual semantic checks
1500 Check_Unreachable_Code
(N
);
1501 Kill_Current_Values
(Last_Assignment_Only
=> True);
1504 Label_Ent
:= Entity
(Label
);
1506 -- Ignore previous error
1508 if Label_Ent
= Any_Id
then
1509 Check_Error_Detected
;
1512 -- We just have a label as the target of a goto
1514 elsif Ekind
(Label_Ent
) /= E_Label
then
1515 Error_Msg_N
("target of goto statement must be a label", Label
);
1518 -- Check that the target of the goto is reachable according to Ada
1519 -- scoping rules. Note: the special gotos we generate for optimizing
1520 -- local handling of exceptions would violate these rules, but we mark
1521 -- such gotos as analyzed when built, so this code is never entered.
1523 elsif not Reachable
(Label_Ent
) then
1524 Error_Msg_N
("target of goto statement is not reachable", Label
);
1528 -- Here if goto passes initial validity checks
1530 Label_Scope
:= Enclosing_Scope
(Label_Ent
);
1532 for J
in reverse 0 .. Scope_Stack
.Last
loop
1533 Scope_Id
:= Scope_Stack
.Table
(J
).Entity
;
1535 if Label_Scope
= Scope_Id
1536 or else not Ekind_In
(Scope_Id
, E_Block
, E_Loop
, E_Return_Statement
)
1538 if Scope_Id
/= Label_Scope
then
1540 ("cannot exit from program unit or accept statement", N
);
1547 raise Program_Error
;
1548 end Analyze_Goto_Statement
;
1550 --------------------------
1551 -- Analyze_If_Statement --
1552 --------------------------
1554 -- A special complication arises in the analysis of if statements
1556 -- The expander has circuitry to completely delete code that it can tell
1557 -- will not be executed (as a result of compile time known conditions). In
1558 -- the analyzer, we ensure that code that will be deleted in this manner
1559 -- is analyzed but not expanded. This is obviously more efficient, but
1560 -- more significantly, difficulties arise if code is expanded and then
1561 -- eliminated (e.g. exception table entries disappear). Similarly, itypes
1562 -- generated in deleted code must be frozen from start, because the nodes
1563 -- on which they depend will not be available at the freeze point.
1565 procedure Analyze_If_Statement
(N
: Node_Id
) is
1568 Save_Unblocked_Exit_Count
: constant Nat
:= Unblocked_Exit_Count
;
1569 -- Recursively save value of this global, will be restored on exit
1571 Save_In_Deleted_Code
: Boolean;
1573 Del
: Boolean := False;
1574 -- This flag gets set True if a True condition has been found, which
1575 -- means that remaining ELSE/ELSIF parts are deleted.
1577 procedure Analyze_Cond_Then
(Cnode
: Node_Id
);
1578 -- This is applied to either the N_If_Statement node itself or to an
1579 -- N_Elsif_Part node. It deals with analyzing the condition and the THEN
1580 -- statements associated with it.
1582 -----------------------
1583 -- Analyze_Cond_Then --
1584 -----------------------
1586 procedure Analyze_Cond_Then
(Cnode
: Node_Id
) is
1587 Cond
: constant Node_Id
:= Condition
(Cnode
);
1588 Tstm
: constant List_Id
:= Then_Statements
(Cnode
);
1591 Unblocked_Exit_Count
:= Unblocked_Exit_Count
+ 1;
1592 Analyze_And_Resolve
(Cond
, Any_Boolean
);
1593 Check_Unset_Reference
(Cond
);
1594 Set_Current_Value_Condition
(Cnode
);
1596 -- If already deleting, then just analyze then statements
1599 Analyze_Statements
(Tstm
);
1601 -- Compile time known value, not deleting yet
1603 elsif Compile_Time_Known_Value
(Cond
) then
1604 Save_In_Deleted_Code
:= In_Deleted_Code
;
1606 -- If condition is True, then analyze the THEN statements and set
1607 -- no expansion for ELSE and ELSIF parts.
1609 if Is_True
(Expr_Value
(Cond
)) then
1610 Analyze_Statements
(Tstm
);
1612 Expander_Mode_Save_And_Set
(False);
1613 In_Deleted_Code
:= True;
1615 -- If condition is False, analyze THEN with expansion off
1617 else -- Is_False (Expr_Value (Cond))
1618 Expander_Mode_Save_And_Set
(False);
1619 In_Deleted_Code
:= True;
1620 Analyze_Statements
(Tstm
);
1621 Expander_Mode_Restore
;
1622 In_Deleted_Code
:= Save_In_Deleted_Code
;
1625 -- Not known at compile time, not deleting, normal analysis
1628 Analyze_Statements
(Tstm
);
1630 end Analyze_Cond_Then
;
1632 -- Start of processing for Analyze_If_Statement
1635 -- Initialize exit count for else statements. If there is no else part,
1636 -- this count will stay non-zero reflecting the fact that the uncovered
1637 -- else case is an unblocked exit.
1639 Unblocked_Exit_Count
:= 1;
1640 Analyze_Cond_Then
(N
);
1642 -- Now to analyze the elsif parts if any are present
1644 if Present
(Elsif_Parts
(N
)) then
1645 E
:= First
(Elsif_Parts
(N
));
1646 while Present
(E
) loop
1647 Analyze_Cond_Then
(E
);
1652 if Present
(Else_Statements
(N
)) then
1653 Analyze_Statements
(Else_Statements
(N
));
1656 -- If all our exits were blocked by unconditional transfers of control,
1657 -- then the entire IF statement acts as an unconditional transfer of
1658 -- control, so treat it like one, and check unreachable code.
1660 if Unblocked_Exit_Count
= 0 then
1661 Unblocked_Exit_Count
:= Save_Unblocked_Exit_Count
;
1662 Check_Unreachable_Code
(N
);
1664 Unblocked_Exit_Count
:= Save_Unblocked_Exit_Count
;
1668 Expander_Mode_Restore
;
1669 In_Deleted_Code
:= Save_In_Deleted_Code
;
1672 if not Expander_Active
1673 and then Compile_Time_Known_Value
(Condition
(N
))
1674 and then Serious_Errors_Detected
= 0
1676 if Is_True
(Expr_Value
(Condition
(N
))) then
1677 Remove_Warning_Messages
(Else_Statements
(N
));
1679 if Present
(Elsif_Parts
(N
)) then
1680 E
:= First
(Elsif_Parts
(N
));
1681 while Present
(E
) loop
1682 Remove_Warning_Messages
(Then_Statements
(E
));
1688 Remove_Warning_Messages
(Then_Statements
(N
));
1692 -- Warn on redundant if statement that has no effect
1694 -- Note, we could also check empty ELSIF parts ???
1696 if Warn_On_Redundant_Constructs
1698 -- If statement must be from source
1700 and then Comes_From_Source
(N
)
1702 -- Condition must not have obvious side effect
1704 and then Has_No_Obvious_Side_Effects
(Condition
(N
))
1706 -- No elsif parts of else part
1708 and then No
(Elsif_Parts
(N
))
1709 and then No
(Else_Statements
(N
))
1711 -- Then must be a single null statement
1713 and then List_Length
(Then_Statements
(N
)) = 1
1715 -- Go to original node, since we may have rewritten something as
1716 -- a null statement (e.g. a case we could figure the outcome of).
1719 T
: constant Node_Id
:= First
(Then_Statements
(N
));
1720 S
: constant Node_Id
:= Original_Node
(T
);
1723 if Comes_From_Source
(S
) and then Nkind
(S
) = N_Null_Statement
then
1724 Error_Msg_N
("if statement has no effect?r?", N
);
1728 end Analyze_If_Statement
;
1730 ----------------------------------------
1731 -- Analyze_Implicit_Label_Declaration --
1732 ----------------------------------------
1734 -- An implicit label declaration is generated in the innermost enclosing
1735 -- declarative part. This is done for labels, and block and loop names.
1737 -- Note: any changes in this routine may need to be reflected in
1738 -- Analyze_Label_Entity.
1740 procedure Analyze_Implicit_Label_Declaration
(N
: Node_Id
) is
1741 Id
: constant Node_Id
:= Defining_Identifier
(N
);
1744 Set_Ekind
(Id
, E_Label
);
1745 Set_Etype
(Id
, Standard_Void_Type
);
1746 Set_Enclosing_Scope
(Id
, Current_Scope
);
1747 end Analyze_Implicit_Label_Declaration
;
1749 ------------------------------
1750 -- Analyze_Iteration_Scheme --
1751 ------------------------------
1753 procedure Analyze_Iteration_Scheme
(N
: Node_Id
) is
1755 Iter_Spec
: Node_Id
;
1756 Loop_Spec
: Node_Id
;
1759 -- For an infinite loop, there is no iteration scheme
1765 Cond
:= Condition
(N
);
1766 Iter_Spec
:= Iterator_Specification
(N
);
1767 Loop_Spec
:= Loop_Parameter_Specification
(N
);
1769 if Present
(Cond
) then
1770 Analyze_And_Resolve
(Cond
, Any_Boolean
);
1771 Check_Unset_Reference
(Cond
);
1772 Set_Current_Value_Condition
(N
);
1774 elsif Present
(Iter_Spec
) then
1775 Analyze_Iterator_Specification
(Iter_Spec
);
1778 Analyze_Loop_Parameter_Specification
(Loop_Spec
);
1780 end Analyze_Iteration_Scheme
;
1782 ------------------------------------
1783 -- Analyze_Iterator_Specification --
1784 ------------------------------------
1786 procedure Analyze_Iterator_Specification
(N
: Node_Id
) is
1787 procedure Check_Reverse_Iteration
(Typ
: Entity_Id
);
1788 -- For an iteration over a container, if the loop carries the Reverse
1789 -- indicator, verify that the container type has an Iterate aspect that
1790 -- implements the reversible iterator interface.
1792 function Get_Cursor_Type
(Typ
: Entity_Id
) return Entity_Id
;
1793 -- For containers with Iterator and related aspects, the cursor is
1794 -- obtained by locating an entity with the proper name in the scope
1797 -----------------------------
1798 -- Check_Reverse_Iteration --
1799 -----------------------------
1801 procedure Check_Reverse_Iteration
(Typ
: Entity_Id
) is
1803 if Reverse_Present
(N
)
1804 and then not Is_Array_Type
(Typ
)
1805 and then not Is_Reversible_Iterator
(Typ
)
1808 ("container type does not support reverse iteration", N
, Typ
);
1810 end Check_Reverse_Iteration
;
1812 ---------------------
1813 -- Get_Cursor_Type --
1814 ---------------------
1816 function Get_Cursor_Type
(Typ
: Entity_Id
) return Entity_Id
is
1820 -- If iterator type is derived, the cursor is declared in the scope
1821 -- of the parent type.
1823 if Is_Derived_Type
(Typ
) then
1824 Ent
:= First_Entity
(Scope
(Etype
(Typ
)));
1826 Ent
:= First_Entity
(Scope
(Typ
));
1829 while Present
(Ent
) loop
1830 exit when Chars
(Ent
) = Name_Cursor
;
1838 -- The cursor is the target of generated assignments in the
1839 -- loop, and cannot have a limited type.
1841 if Is_Limited_Type
(Etype
(Ent
)) then
1842 Error_Msg_N
("cursor type cannot be limited", N
);
1846 end Get_Cursor_Type
;
1850 Def_Id
: constant Node_Id
:= Defining_Identifier
(N
);
1851 Iter_Name
: constant Node_Id
:= Name
(N
);
1852 Loc
: constant Source_Ptr
:= Sloc
(N
);
1853 Subt
: constant Node_Id
:= Subtype_Indication
(N
);
1858 -- Start of processing for Analyze_Iterator_Specification
1861 Enter_Name
(Def_Id
);
1863 -- AI12-0151 specifies that when the subtype indication is present, it
1864 -- must statically match the type of the array or container element.
1865 -- To simplify this check, we introduce a subtype declaration with the
1866 -- given subtype indication when it carries a constraint, and rewrite
1867 -- the original as a reference to the created subtype entity.
1869 if Present
(Subt
) then
1870 if Nkind
(Subt
) = N_Subtype_Indication
then
1872 S
: constant Entity_Id
:= Make_Temporary
(Sloc
(Subt
), 'S');
1873 Decl
: constant Node_Id
:=
1874 Make_Subtype_Declaration
(Loc
,
1875 Defining_Identifier
=> S
,
1876 Subtype_Indication
=> New_Copy_Tree
(Subt
));
1878 Insert_Before
(Parent
(Parent
(N
)), Decl
);
1880 Rewrite
(Subt
, New_Occurrence_Of
(S
, Sloc
(Subt
)));
1886 -- Save entity of subtype indication for subsequent check
1888 Bas
:= Entity
(Subt
);
1891 Preanalyze_Range
(Iter_Name
);
1893 -- Set the kind of the loop variable, which is not visible within
1894 -- the iterator name.
1896 Set_Ekind
(Def_Id
, E_Variable
);
1898 -- Provide a link between the iterator variable and the container, for
1899 -- subsequent use in cross-reference and modification information.
1901 if Of_Present
(N
) then
1902 Set_Related_Expression
(Def_Id
, Iter_Name
);
1904 -- For a container, the iterator is specified through the aspect
1906 if not Is_Array_Type
(Etype
(Iter_Name
)) then
1908 Iterator
: constant Entity_Id
:=
1909 Find_Value_Of_Aspect
1910 (Etype
(Iter_Name
), Aspect_Default_Iterator
);
1916 if No
(Iterator
) then
1917 null; -- error reported below.
1919 elsif not Is_Overloaded
(Iterator
) then
1920 Check_Reverse_Iteration
(Etype
(Iterator
));
1922 -- If Iterator is overloaded, use reversible iterator if
1923 -- one is available.
1925 elsif Is_Overloaded
(Iterator
) then
1926 Get_First_Interp
(Iterator
, I
, It
);
1927 while Present
(It
.Nam
) loop
1928 if Ekind
(It
.Nam
) = E_Function
1929 and then Is_Reversible_Iterator
(Etype
(It
.Nam
))
1931 Set_Etype
(Iterator
, It
.Typ
);
1932 Set_Entity
(Iterator
, It
.Nam
);
1936 Get_Next_Interp
(I
, It
);
1939 Check_Reverse_Iteration
(Etype
(Iterator
));
1945 -- If the domain of iteration is an expression, create a declaration for
1946 -- it, so that finalization actions are introduced outside of the loop.
1947 -- The declaration must be a renaming because the body of the loop may
1948 -- assign to elements.
1950 if not Is_Entity_Name
(Iter_Name
)
1952 -- When the context is a quantified expression, the renaming
1953 -- declaration is delayed until the expansion phase if we are
1956 and then (Nkind
(Parent
(N
)) /= N_Quantified_Expression
1957 or else Operating_Mode
= Check_Semantics
)
1959 -- Do not perform this expansion for ASIS and when expansion is
1960 -- disabled, where the temporary may hide the transformation of a
1961 -- selected component into a prefixed function call, and references
1962 -- need to see the original expression.
1964 and then Expander_Active
1967 Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'R', Iter_Name
);
1973 -- If the domain of iteration is an array component that depends
1974 -- on a discriminant, create actual subtype for it. Pre-analysis
1975 -- does not generate the actual subtype of a selected component.
1977 if Nkind
(Iter_Name
) = N_Selected_Component
1978 and then Is_Array_Type
(Etype
(Iter_Name
))
1981 Build_Actual_Subtype_Of_Component
1982 (Etype
(Selector_Name
(Iter_Name
)), Iter_Name
);
1983 Insert_Action
(N
, Act_S
);
1985 if Present
(Act_S
) then
1986 Typ
:= Defining_Identifier
(Act_S
);
1988 Typ
:= Etype
(Iter_Name
);
1992 Typ
:= Etype
(Iter_Name
);
1994 -- Verify that the expression produces an iterator
1996 if not Of_Present
(N
) and then not Is_Iterator
(Typ
)
1997 and then not Is_Array_Type
(Typ
)
1998 and then No
(Find_Aspect
(Typ
, Aspect_Iterable
))
2001 ("expect object that implements iterator interface",
2006 -- Protect against malformed iterator
2008 if Typ
= Any_Type
then
2009 Error_Msg_N
("invalid expression in loop iterator", Iter_Name
);
2013 if not Of_Present
(N
) then
2014 Check_Reverse_Iteration
(Typ
);
2017 -- The name in the renaming declaration may be a function call.
2018 -- Indicate that it does not come from source, to suppress
2019 -- spurious warnings on renamings of parameterless functions,
2020 -- a common enough idiom in user-defined iterators.
2023 Make_Object_Renaming_Declaration
(Loc
,
2024 Defining_Identifier
=> Id
,
2025 Subtype_Mark
=> New_Occurrence_Of
(Typ
, Loc
),
2027 New_Copy_Tree
(Iter_Name
, New_Sloc
=> Loc
));
2029 Insert_Actions
(Parent
(Parent
(N
)), New_List
(Decl
));
2030 Rewrite
(Name
(N
), New_Occurrence_Of
(Id
, Loc
));
2031 Set_Etype
(Id
, Typ
);
2032 Set_Etype
(Name
(N
), Typ
);
2035 -- Container is an entity or an array with uncontrolled components, or
2036 -- else it is a container iterator given by a function call, typically
2037 -- called Iterate in the case of predefined containers, even though
2038 -- Iterate is not a reserved name. What matters is that the return type
2039 -- of the function is an iterator type.
2041 elsif Is_Entity_Name
(Iter_Name
) then
2042 Analyze
(Iter_Name
);
2044 if Nkind
(Iter_Name
) = N_Function_Call
then
2046 C
: constant Node_Id
:= Name
(Iter_Name
);
2051 if not Is_Overloaded
(Iter_Name
) then
2052 Resolve
(Iter_Name
, Etype
(C
));
2055 Get_First_Interp
(C
, I
, It
);
2056 while It
.Typ
/= Empty
loop
2057 if Reverse_Present
(N
) then
2058 if Is_Reversible_Iterator
(It
.Typ
) then
2059 Resolve
(Iter_Name
, It
.Typ
);
2063 elsif Is_Iterator
(It
.Typ
) then
2064 Resolve
(Iter_Name
, It
.Typ
);
2068 Get_Next_Interp
(I
, It
);
2073 -- Domain of iteration is not overloaded
2076 Resolve
(Iter_Name
, Etype
(Iter_Name
));
2079 if not Of_Present
(N
) then
2080 Check_Reverse_Iteration
(Etype
(Iter_Name
));
2084 -- Get base type of container, for proper retrieval of Cursor type
2085 -- and primitive operations.
2087 Typ
:= Base_Type
(Etype
(Iter_Name
));
2089 if Is_Array_Type
(Typ
) then
2090 if Of_Present
(N
) then
2091 Set_Etype
(Def_Id
, Component_Type
(Typ
));
2093 -- The loop variable is aliased if the array components are
2096 Set_Is_Aliased
(Def_Id
, Has_Aliased_Components
(Typ
));
2098 -- AI12-0047 stipulates that the domain (array or container)
2099 -- cannot be a component that depends on a discriminant if the
2100 -- enclosing object is mutable, to prevent a modification of the
2101 -- dowmain of iteration in the course of an iteration.
2103 -- If the object is an expression it has been captured in a
2104 -- temporary, so examine original node.
2106 if Nkind
(Original_Node
(Iter_Name
)) = N_Selected_Component
2107 and then Is_Dependent_Component_Of_Mutable_Object
2108 (Original_Node
(Iter_Name
))
2111 ("iterable name cannot be a discriminant-dependent "
2112 & "component of a mutable object", N
);
2117 (Base_Type
(Bas
) /= Base_Type
(Component_Type
(Typ
))
2119 not Subtypes_Statically_Match
(Bas
, Component_Type
(Typ
)))
2122 ("subtype indication does not match component type", Subt
);
2125 -- Here we have a missing Range attribute
2129 ("missing Range attribute in iteration over an array", N
);
2131 -- In Ada 2012 mode, this may be an attempt at an iterator
2133 if Ada_Version
>= Ada_2012
then
2135 ("\if& is meant to designate an element of the array, use OF",
2139 -- Prevent cascaded errors
2141 Set_Ekind
(Def_Id
, E_Loop_Parameter
);
2142 Set_Etype
(Def_Id
, Etype
(First_Index
(Typ
)));
2145 -- Check for type error in iterator
2147 elsif Typ
= Any_Type
then
2150 -- Iteration over a container
2153 Set_Ekind
(Def_Id
, E_Loop_Parameter
);
2154 Error_Msg_Ada_2012_Feature
("container iterator", Sloc
(N
));
2158 if Of_Present
(N
) then
2159 if Has_Aspect
(Typ
, Aspect_Iterable
) then
2161 Elt
: constant Entity_Id
:=
2162 Get_Iterable_Type_Primitive
(Typ
, Name_Element
);
2166 ("missing Element primitive for iteration", N
);
2168 Set_Etype
(Def_Id
, Etype
(Elt
));
2172 -- For a predefined container, The type of the loop variable is
2173 -- the Iterator_Element aspect of the container type.
2177 Element
: constant Entity_Id
:=
2178 Find_Value_Of_Aspect
2179 (Typ
, Aspect_Iterator_Element
);
2180 Iterator
: constant Entity_Id
:=
2181 Find_Value_Of_Aspect
2182 (Typ
, Aspect_Default_Iterator
);
2183 Orig_Iter_Name
: constant Node_Id
:=
2184 Original_Node
(Iter_Name
);
2185 Cursor_Type
: Entity_Id
;
2188 if No
(Element
) then
2189 Error_Msg_NE
("cannot iterate over&", N
, Typ
);
2193 Set_Etype
(Def_Id
, Entity
(Element
));
2194 Cursor_Type
:= Get_Cursor_Type
(Typ
);
2195 pragma Assert
(Present
(Cursor_Type
));
2197 -- If subtype indication was given, verify that it covers
2198 -- the element type of the container.
2201 and then (not Covers
(Bas
, Etype
(Def_Id
))
2202 or else not Subtypes_Statically_Match
2203 (Bas
, Etype
(Def_Id
)))
2206 ("subtype indication does not match element type",
2210 -- If the container has a variable indexing aspect, the
2211 -- element is a variable and is modifiable in the loop.
2213 if Has_Aspect
(Typ
, Aspect_Variable_Indexing
) then
2214 Set_Ekind
(Def_Id
, E_Variable
);
2217 -- If the container is a constant, iterating over it
2218 -- requires a Constant_Indexing operation.
2220 if not Is_Variable
(Iter_Name
)
2221 and then not Has_Aspect
(Typ
, Aspect_Constant_Indexing
)
2224 ("iteration over constant container require "
2225 & "constant_indexing aspect", N
);
2227 -- The Iterate function may have an in_out parameter,
2228 -- and a constant container is thus illegal.
2230 elsif Present
(Iterator
)
2231 and then Ekind
(Entity
(Iterator
)) = E_Function
2232 and then Ekind
(First_Formal
(Entity
(Iterator
))) /=
2234 and then not Is_Variable
(Iter_Name
)
2236 Error_Msg_N
("variable container expected", N
);
2239 -- Detect a case where the iterator denotes a component
2240 -- of a mutable object which depends on a discriminant.
2241 -- Note that the iterator may denote a function call in
2242 -- qualified form, in which case this check should not
2245 if Nkind
(Orig_Iter_Name
) = N_Selected_Component
2247 Present
(Entity
(Selector_Name
(Orig_Iter_Name
)))
2249 (Entity
(Selector_Name
(Orig_Iter_Name
)),
2252 and then Is_Dependent_Component_Of_Mutable_Object
2256 ("container cannot be a discriminant-dependent "
2257 & "component of a mutable object", N
);
2263 -- IN iterator, domain is a range, or a call to Iterate function
2266 -- For an iteration of the form IN, the name must denote an
2267 -- iterator, typically the result of a call to Iterate. Give a
2268 -- useful error message when the name is a container by itself.
2270 -- The type may be a formal container type, which has to have
2271 -- an Iterable aspect detailing the required primitives.
2273 if Is_Entity_Name
(Original_Node
(Name
(N
)))
2274 and then not Is_Iterator
(Typ
)
2276 if Has_Aspect
(Typ
, Aspect_Iterable
) then
2279 elsif not Has_Aspect
(Typ
, Aspect_Iterator_Element
) then
2281 ("cannot iterate over&", Name
(N
), Typ
);
2284 ("name must be an iterator, not a container", Name
(N
));
2287 if Has_Aspect
(Typ
, Aspect_Iterable
) then
2291 ("\to iterate directly over the elements of a container, "
2292 & "write `of &`", Name
(N
), Original_Node
(Name
(N
)));
2294 -- No point in continuing analysis of iterator spec
2300 -- If the name is a call (typically prefixed) to some Iterate
2301 -- function, it has been rewritten as an object declaration.
2302 -- If that object is a selected component, verify that it is not
2303 -- a component of an unconstrained mutable object.
2305 if Nkind
(Iter_Name
) = N_Identifier
2306 or else (not Expander_Active
and Comes_From_Source
(Iter_Name
))
2309 Orig_Node
: constant Node_Id
:= Original_Node
(Iter_Name
);
2310 Iter_Kind
: constant Node_Kind
:= Nkind
(Orig_Node
);
2314 if Iter_Kind
= N_Selected_Component
then
2315 Obj
:= Prefix
(Orig_Node
);
2317 elsif Iter_Kind
= N_Function_Call
then
2318 Obj
:= First_Actual
(Orig_Node
);
2320 -- If neither, the name comes from source
2326 if Nkind
(Obj
) = N_Selected_Component
2327 and then Is_Dependent_Component_Of_Mutable_Object
(Obj
)
2330 ("container cannot be a discriminant-dependent "
2331 & "component of a mutable object", N
);
2336 -- The result type of Iterate function is the classwide type of
2337 -- the interface parent. We need the specific Cursor type defined
2338 -- in the container package. We obtain it by name for a predefined
2339 -- container, or through the Iterable aspect for a formal one.
2341 if Has_Aspect
(Typ
, Aspect_Iterable
) then
2344 (Parent
(Find_Value_Of_Aspect
(Typ
, Aspect_Iterable
)),
2348 Set_Etype
(Def_Id
, Get_Cursor_Type
(Typ
));
2349 Check_Reverse_Iteration
(Etype
(Iter_Name
));
2354 end Analyze_Iterator_Specification
;
2360 -- Note: the semantic work required for analyzing labels (setting them as
2361 -- reachable) was done in a prepass through the statements in the block,
2362 -- so that forward gotos would be properly handled. See Analyze_Statements
2363 -- for further details. The only processing required here is to deal with
2364 -- optimizations that depend on an assumption of sequential control flow,
2365 -- since of course the occurrence of a label breaks this assumption.
2367 procedure Analyze_Label
(N
: Node_Id
) is
2368 pragma Warnings
(Off
, N
);
2370 Kill_Current_Values
;
2373 --------------------------
2374 -- Analyze_Label_Entity --
2375 --------------------------
2377 procedure Analyze_Label_Entity
(E
: Entity_Id
) is
2379 Set_Ekind
(E
, E_Label
);
2380 Set_Etype
(E
, Standard_Void_Type
);
2381 Set_Enclosing_Scope
(E
, Current_Scope
);
2382 Set_Reachable
(E
, True);
2383 end Analyze_Label_Entity
;
2385 ------------------------------------------
2386 -- Analyze_Loop_Parameter_Specification --
2387 ------------------------------------------
2389 procedure Analyze_Loop_Parameter_Specification
(N
: Node_Id
) is
2390 Loop_Nod
: constant Node_Id
:= Parent
(Parent
(N
));
2392 procedure Check_Controlled_Array_Attribute
(DS
: Node_Id
);
2393 -- If the bounds are given by a 'Range reference on a function call
2394 -- that returns a controlled array, introduce an explicit declaration
2395 -- to capture the bounds, so that the function result can be finalized
2396 -- in timely fashion.
2398 procedure Check_Predicate_Use
(T
: Entity_Id
);
2399 -- Diagnose Attempt to iterate through non-static predicate. Note that
2400 -- a type with inherited predicates may have both static and dynamic
2401 -- forms. In this case it is not sufficent to check the static predicate
2402 -- function only, look for a dynamic predicate aspect as well.
2404 function Has_Call_Using_Secondary_Stack
(N
: Node_Id
) return Boolean;
2405 -- N is the node for an arbitrary construct. This function searches the
2406 -- construct N to see if any expressions within it contain function
2407 -- calls that use the secondary stack, returning True if any such call
2408 -- is found, and False otherwise.
2410 procedure Process_Bounds
(R
: Node_Id
);
2411 -- If the iteration is given by a range, create temporaries and
2412 -- assignment statements block to capture the bounds and perform
2413 -- required finalization actions in case a bound includes a function
2414 -- call that uses the temporary stack. We first pre-analyze a copy of
2415 -- the range in order to determine the expected type, and analyze and
2416 -- resolve the original bounds.
2418 --------------------------------------
2419 -- Check_Controlled_Array_Attribute --
2420 --------------------------------------
2422 procedure Check_Controlled_Array_Attribute
(DS
: Node_Id
) is
2424 if Nkind
(DS
) = N_Attribute_Reference
2425 and then Is_Entity_Name
(Prefix
(DS
))
2426 and then Ekind
(Entity
(Prefix
(DS
))) = E_Function
2427 and then Is_Array_Type
(Etype
(Entity
(Prefix
(DS
))))
2429 Is_Controlled
(Component_Type
(Etype
(Entity
(Prefix
(DS
)))))
2430 and then Expander_Active
2433 Loc
: constant Source_Ptr
:= Sloc
(N
);
2434 Arr
: constant Entity_Id
:= Etype
(Entity
(Prefix
(DS
)));
2435 Indx
: constant Entity_Id
:=
2436 Base_Type
(Etype
(First_Index
(Arr
)));
2437 Subt
: constant Entity_Id
:= Make_Temporary
(Loc
, 'S');
2442 Make_Subtype_Declaration
(Loc
,
2443 Defining_Identifier
=> Subt
,
2444 Subtype_Indication
=>
2445 Make_Subtype_Indication
(Loc
,
2446 Subtype_Mark
=> New_Occurrence_Of
(Indx
, Loc
),
2448 Make_Range_Constraint
(Loc
, Relocate_Node
(DS
))));
2449 Insert_Before
(Loop_Nod
, Decl
);
2453 Make_Attribute_Reference
(Loc
,
2454 Prefix
=> New_Occurrence_Of
(Subt
, Loc
),
2455 Attribute_Name
=> Attribute_Name
(DS
)));
2460 end Check_Controlled_Array_Attribute
;
2462 -------------------------
2463 -- Check_Predicate_Use --
2464 -------------------------
2466 procedure Check_Predicate_Use
(T
: Entity_Id
) is
2468 -- A predicated subtype is illegal in loops and related constructs
2469 -- if the predicate is not static, or if it is a non-static subtype
2470 -- of a statically predicated subtype.
2472 if Is_Discrete_Type
(T
)
2473 and then Has_Predicates
(T
)
2474 and then (not Has_Static_Predicate
(T
)
2475 or else not Is_Static_Subtype
(T
)
2476 or else Has_Dynamic_Predicate_Aspect
(T
))
2478 -- Seems a confusing message for the case of a static predicate
2479 -- with a non-static subtype???
2481 Bad_Predicated_Subtype_Use
2482 ("cannot use subtype& with non-static predicate for loop "
2483 & "iteration", Discrete_Subtype_Definition
(N
),
2484 T
, Suggest_Static
=> True);
2486 elsif Inside_A_Generic
and then Is_Generic_Formal
(T
) then
2487 Set_No_Dynamic_Predicate_On_Actual
(T
);
2489 end Check_Predicate_Use
;
2491 ------------------------------------
2492 -- Has_Call_Using_Secondary_Stack --
2493 ------------------------------------
2495 function Has_Call_Using_Secondary_Stack
(N
: Node_Id
) return Boolean is
2497 function Check_Call
(N
: Node_Id
) return Traverse_Result
;
2498 -- Check if N is a function call which uses the secondary stack
2504 function Check_Call
(N
: Node_Id
) return Traverse_Result
is
2507 Return_Typ
: Entity_Id
;
2510 if Nkind
(N
) = N_Function_Call
then
2513 -- Call using access to subprogram with explicit dereference
2515 if Nkind
(Nam
) = N_Explicit_Dereference
then
2516 Subp
:= Etype
(Nam
);
2518 -- Call using a selected component notation or Ada 2005 object
2519 -- operation notation
2521 elsif Nkind
(Nam
) = N_Selected_Component
then
2522 Subp
:= Entity
(Selector_Name
(Nam
));
2527 Subp
:= Entity
(Nam
);
2530 Return_Typ
:= Etype
(Subp
);
2532 if Is_Composite_Type
(Return_Typ
)
2533 and then not Is_Constrained
(Return_Typ
)
2537 elsif Sec_Stack_Needed_For_Return
(Subp
) then
2542 -- Continue traversing the tree
2547 function Check_Calls
is new Traverse_Func
(Check_Call
);
2549 -- Start of processing for Has_Call_Using_Secondary_Stack
2552 return Check_Calls
(N
) = Abandon
;
2553 end Has_Call_Using_Secondary_Stack
;
2555 --------------------
2556 -- Process_Bounds --
2557 --------------------
2559 procedure Process_Bounds
(R
: Node_Id
) is
2560 Loc
: constant Source_Ptr
:= Sloc
(N
);
2563 (Original_Bound
: Node_Id
;
2564 Analyzed_Bound
: Node_Id
;
2565 Typ
: Entity_Id
) return Node_Id
;
2566 -- Capture value of bound and return captured value
2573 (Original_Bound
: Node_Id
;
2574 Analyzed_Bound
: Node_Id
;
2575 Typ
: Entity_Id
) return Node_Id
2582 -- If the bound is a constant or an object, no need for a separate
2583 -- declaration. If the bound is the result of previous expansion
2584 -- it is already analyzed and should not be modified. Note that
2585 -- the Bound will be resolved later, if needed, as part of the
2586 -- call to Make_Index (literal bounds may need to be resolved to
2589 if Analyzed
(Original_Bound
) then
2590 return Original_Bound
;
2592 elsif Nkind_In
(Analyzed_Bound
, N_Integer_Literal
,
2593 N_Character_Literal
)
2594 or else Is_Entity_Name
(Analyzed_Bound
)
2596 Analyze_And_Resolve
(Original_Bound
, Typ
);
2597 return Original_Bound
;
2600 -- Normally, the best approach is simply to generate a constant
2601 -- declaration that captures the bound. However, there is a nasty
2602 -- case where this is wrong. If the bound is complex, and has a
2603 -- possible use of the secondary stack, we need to generate a
2604 -- separate assignment statement to ensure the creation of a block
2605 -- which will release the secondary stack.
2607 -- We prefer the constant declaration, since it leaves us with a
2608 -- proper trace of the value, useful in optimizations that get rid
2609 -- of junk range checks.
2611 if not Has_Call_Using_Secondary_Stack
(Analyzed_Bound
) then
2612 Analyze_And_Resolve
(Original_Bound
, Typ
);
2614 -- Ensure that the bound is valid. This check should not be
2615 -- generated when the range belongs to a quantified expression
2616 -- as the construct is still not expanded into its final form.
2618 if Nkind
(Parent
(R
)) /= N_Loop_Parameter_Specification
2619 or else Nkind
(Parent
(Parent
(R
))) /= N_Quantified_Expression
2621 Ensure_Valid
(Original_Bound
);
2624 Force_Evaluation
(Original_Bound
);
2625 return Original_Bound
;
2628 Id
:= Make_Temporary
(Loc
, 'R', Original_Bound
);
2630 -- Here we make a declaration with a separate assignment
2631 -- statement, and insert before loop header.
2634 Make_Object_Declaration
(Loc
,
2635 Defining_Identifier
=> Id
,
2636 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
2639 Make_Assignment_Statement
(Loc
,
2640 Name
=> New_Occurrence_Of
(Id
, Loc
),
2641 Expression
=> Relocate_Node
(Original_Bound
));
2643 Insert_Actions
(Loop_Nod
, New_List
(Decl
, Assign
));
2645 -- Now that this temporary variable is initialized we decorate it
2646 -- as safe-to-reevaluate to inform to the backend that no further
2647 -- asignment will be issued and hence it can be handled as side
2648 -- effect free. Note that this decoration must be done when the
2649 -- assignment has been analyzed because otherwise it will be
2650 -- rejected (see Analyze_Assignment).
2652 Set_Is_Safe_To_Reevaluate
(Id
);
2654 Rewrite
(Original_Bound
, New_Occurrence_Of
(Id
, Loc
));
2656 if Nkind
(Assign
) = N_Assignment_Statement
then
2657 return Expression
(Assign
);
2659 return Original_Bound
;
2663 Hi
: constant Node_Id
:= High_Bound
(R
);
2664 Lo
: constant Node_Id
:= Low_Bound
(R
);
2665 R_Copy
: constant Node_Id
:= New_Copy_Tree
(R
);
2670 -- Start of processing for Process_Bounds
2673 Set_Parent
(R_Copy
, Parent
(R
));
2674 Preanalyze_Range
(R_Copy
);
2675 Typ
:= Etype
(R_Copy
);
2677 -- If the type of the discrete range is Universal_Integer, then the
2678 -- bound's type must be resolved to Integer, and any object used to
2679 -- hold the bound must also have type Integer, unless the literal
2680 -- bounds are constant-folded expressions with a user-defined type.
2682 if Typ
= Universal_Integer
then
2683 if Nkind
(Lo
) = N_Integer_Literal
2684 and then Present
(Etype
(Lo
))
2685 and then Scope
(Etype
(Lo
)) /= Standard_Standard
2689 elsif Nkind
(Hi
) = N_Integer_Literal
2690 and then Present
(Etype
(Hi
))
2691 and then Scope
(Etype
(Hi
)) /= Standard_Standard
2696 Typ
:= Standard_Integer
;
2702 New_Lo
:= One_Bound
(Lo
, Low_Bound
(R_Copy
), Typ
);
2703 New_Hi
:= One_Bound
(Hi
, High_Bound
(R_Copy
), Typ
);
2705 -- Propagate staticness to loop range itself, in case the
2706 -- corresponding subtype is static.
2708 if New_Lo
/= Lo
and then Is_OK_Static_Expression
(New_Lo
) then
2709 Rewrite
(Low_Bound
(R
), New_Copy
(New_Lo
));
2712 if New_Hi
/= Hi
and then Is_OK_Static_Expression
(New_Hi
) then
2713 Rewrite
(High_Bound
(R
), New_Copy
(New_Hi
));
2719 DS
: constant Node_Id
:= Discrete_Subtype_Definition
(N
);
2720 Id
: constant Entity_Id
:= Defining_Identifier
(N
);
2724 -- Start of processing for Analyze_Loop_Parameter_Specification
2729 -- We always consider the loop variable to be referenced, since the loop
2730 -- may be used just for counting purposes.
2732 Generate_Reference
(Id
, N
, ' ');
2734 -- Check for the case of loop variable hiding a local variable (used
2735 -- later on to give a nice warning if the hidden variable is never
2739 H
: constant Entity_Id
:= Homonym
(Id
);
2742 and then Ekind
(H
) = E_Variable
2743 and then Is_Discrete_Type
(Etype
(H
))
2744 and then Enclosing_Dynamic_Scope
(H
) = Enclosing_Dynamic_Scope
(Id
)
2746 Set_Hiding_Loop_Variable
(H
, Id
);
2750 -- Loop parameter specification must include subtype mark in SPARK
2752 if Nkind
(DS
) = N_Range
then
2753 Check_SPARK_05_Restriction
2754 ("loop parameter specification must include subtype mark", N
);
2757 -- Analyze the subtype definition and create temporaries for the bounds.
2758 -- Do not evaluate the range when preanalyzing a quantified expression
2759 -- because bounds expressed as function calls with side effects will be
2760 -- incorrectly replicated.
2762 if Nkind
(DS
) = N_Range
2763 and then Expander_Active
2764 and then Nkind
(Parent
(N
)) /= N_Quantified_Expression
2766 Process_Bounds
(DS
);
2768 -- Either the expander not active or the range of iteration is a subtype
2769 -- indication, an entity, or a function call that yields an aggregate or
2773 DS_Copy
:= New_Copy_Tree
(DS
);
2774 Set_Parent
(DS_Copy
, Parent
(DS
));
2775 Preanalyze_Range
(DS_Copy
);
2777 -- Ada 2012: If the domain of iteration is:
2779 -- a) a function call,
2780 -- b) an identifier that is not a type,
2781 -- c) an attribute reference 'Old (within a postcondition),
2782 -- d) an unchecked conversion or a qualified expression with
2783 -- the proper iterator type.
2785 -- then it is an iteration over a container. It was classified as
2786 -- a loop specification by the parser, and must be rewritten now
2787 -- to activate container iteration. The last case will occur within
2788 -- an expanded inlined call, where the expansion wraps an actual in
2789 -- an unchecked conversion when needed. The expression of the
2790 -- conversion is always an object.
2792 if Nkind
(DS_Copy
) = N_Function_Call
2794 or else (Is_Entity_Name
(DS_Copy
)
2795 and then not Is_Type
(Entity
(DS_Copy
)))
2797 or else (Nkind
(DS_Copy
) = N_Attribute_Reference
2798 and then Nam_In
(Attribute_Name
(DS_Copy
),
2799 Name_Loop_Entry
, Name_Old
))
2801 or else Has_Aspect
(Etype
(DS_Copy
), Aspect_Iterable
)
2803 or else Nkind
(DS_Copy
) = N_Unchecked_Type_Conversion
2804 or else (Nkind
(DS_Copy
) = N_Qualified_Expression
2805 and then Is_Iterator
(Etype
(DS_Copy
)))
2807 -- This is an iterator specification. Rewrite it as such and
2808 -- analyze it to capture function calls that may require
2809 -- finalization actions.
2812 I_Spec
: constant Node_Id
:=
2813 Make_Iterator_Specification
(Sloc
(N
),
2814 Defining_Identifier
=> Relocate_Node
(Id
),
2816 Subtype_Indication
=> Empty
,
2817 Reverse_Present
=> Reverse_Present
(N
));
2818 Scheme
: constant Node_Id
:= Parent
(N
);
2821 Set_Iterator_Specification
(Scheme
, I_Spec
);
2822 Set_Loop_Parameter_Specification
(Scheme
, Empty
);
2823 Analyze_Iterator_Specification
(I_Spec
);
2825 -- In a generic context, analyze the original domain of
2826 -- iteration, for name capture.
2828 if not Expander_Active
then
2832 -- Set kind of loop parameter, which may be used in the
2833 -- subsequent analysis of the condition in a quantified
2836 Set_Ekind
(Id
, E_Loop_Parameter
);
2840 -- Domain of iteration is not a function call, and is side-effect
2844 -- A quantified expression that appears in a pre/post condition
2845 -- is pre-analyzed several times. If the range is given by an
2846 -- attribute reference it is rewritten as a range, and this is
2847 -- done even with expansion disabled. If the type is already set
2848 -- do not reanalyze, because a range with static bounds may be
2849 -- typed Integer by default.
2851 if Nkind
(Parent
(N
)) = N_Quantified_Expression
2852 and then Present
(Etype
(DS
))
2865 -- Some additional checks if we are iterating through a type
2867 if Is_Entity_Name
(DS
)
2868 and then Present
(Entity
(DS
))
2869 and then Is_Type
(Entity
(DS
))
2871 -- The subtype indication may denote the completion of an incomplete
2872 -- type declaration.
2874 if Ekind
(Entity
(DS
)) = E_Incomplete_Type
then
2875 Set_Entity
(DS
, Get_Full_View
(Entity
(DS
)));
2876 Set_Etype
(DS
, Entity
(DS
));
2879 Check_Predicate_Use
(Entity
(DS
));
2882 -- Error if not discrete type
2884 if not Is_Discrete_Type
(Etype
(DS
)) then
2885 Wrong_Type
(DS
, Any_Discrete
);
2886 Set_Etype
(DS
, Any_Type
);
2889 Check_Controlled_Array_Attribute
(DS
);
2891 if Nkind
(DS
) = N_Subtype_Indication
then
2892 Check_Predicate_Use
(Entity
(Subtype_Mark
(DS
)));
2895 Make_Index
(DS
, N
, In_Iter_Schm
=> True);
2896 Set_Ekind
(Id
, E_Loop_Parameter
);
2898 -- A quantified expression which appears in a pre- or post-condition may
2899 -- be analyzed multiple times. The analysis of the range creates several
2900 -- itypes which reside in different scopes depending on whether the pre-
2901 -- or post-condition has been expanded. Update the type of the loop
2902 -- variable to reflect the proper itype at each stage of analysis.
2905 or else Etype
(Id
) = Any_Type
2907 (Present
(Etype
(Id
))
2908 and then Is_Itype
(Etype
(Id
))
2909 and then Nkind
(Parent
(Loop_Nod
)) = N_Expression_With_Actions
2910 and then Nkind
(Original_Node
(Parent
(Loop_Nod
))) =
2911 N_Quantified_Expression
)
2913 Set_Etype
(Id
, Etype
(DS
));
2916 -- Treat a range as an implicit reference to the type, to inhibit
2917 -- spurious warnings.
2919 Generate_Reference
(Base_Type
(Etype
(DS
)), N
, ' ');
2920 Set_Is_Known_Valid
(Id
, True);
2922 -- The loop is not a declarative part, so the loop variable must be
2923 -- frozen explicitly. Do not freeze while preanalyzing a quantified
2924 -- expression because the freeze node will not be inserted into the
2925 -- tree due to flag Is_Spec_Expression being set.
2927 if Nkind
(Parent
(N
)) /= N_Quantified_Expression
then
2929 Flist
: constant List_Id
:= Freeze_Entity
(Id
, N
);
2931 if Is_Non_Empty_List
(Flist
) then
2932 Insert_Actions
(N
, Flist
);
2937 -- Case where we have a range or a subtype, get type bounds
2939 if Nkind_In
(DS
, N_Range
, N_Subtype_Indication
)
2940 and then not Error_Posted
(DS
)
2941 and then Etype
(DS
) /= Any_Type
2942 and then Is_Discrete_Type
(Etype
(DS
))
2949 if Nkind
(DS
) = N_Range
then
2950 L
:= Low_Bound
(DS
);
2951 H
:= High_Bound
(DS
);
2954 Type_Low_Bound
(Underlying_Type
(Etype
(Subtype_Mark
(DS
))));
2956 Type_High_Bound
(Underlying_Type
(Etype
(Subtype_Mark
(DS
))));
2959 -- Check for null or possibly null range and issue warning. We
2960 -- suppress such messages in generic templates and instances,
2961 -- because in practice they tend to be dubious in these cases. The
2962 -- check applies as well to rewritten array element loops where a
2963 -- null range may be detected statically.
2965 if Compile_Time_Compare
(L
, H
, Assume_Valid
=> True) = GT
then
2967 -- Suppress the warning if inside a generic template or
2968 -- instance, since in practice they tend to be dubious in these
2969 -- cases since they can result from intended parameterization.
2971 if not Inside_A_Generic
and then not In_Instance
then
2973 -- Specialize msg if invalid values could make the loop
2974 -- non-null after all.
2976 if Compile_Time_Compare
2977 (L
, H
, Assume_Valid
=> False) = GT
2979 -- Since we know the range of the loop is null, set the
2980 -- appropriate flag to remove the loop entirely during
2983 Set_Is_Null_Loop
(Loop_Nod
);
2985 if Comes_From_Source
(N
) then
2987 ("??loop range is null, loop will not execute", DS
);
2990 -- Here is where the loop could execute because of
2991 -- invalid values, so issue appropriate message and in
2992 -- this case we do not set the Is_Null_Loop flag since
2993 -- the loop may execute.
2995 elsif Comes_From_Source
(N
) then
2997 ("??loop range may be null, loop may not execute",
3000 ("??can only execute if invalid values are present",
3005 -- In either case, suppress warnings in the body of the loop,
3006 -- since it is likely that these warnings will be inappropriate
3007 -- if the loop never actually executes, which is likely.
3009 Set_Suppress_Loop_Warnings
(Loop_Nod
);
3011 -- The other case for a warning is a reverse loop where the
3012 -- upper bound is the integer literal zero or one, and the
3013 -- lower bound may exceed this value.
3015 -- For example, we have
3017 -- for J in reverse N .. 1 loop
3019 -- In practice, this is very likely to be a case of reversing
3020 -- the bounds incorrectly in the range.
3022 elsif Reverse_Present
(N
)
3023 and then Nkind
(Original_Node
(H
)) = N_Integer_Literal
3025 (Intval
(Original_Node
(H
)) = Uint_0
3027 Intval
(Original_Node
(H
)) = Uint_1
)
3029 -- Lower bound may in fact be known and known not to exceed
3030 -- upper bound (e.g. reverse 0 .. 1) and that's OK.
3032 if Compile_Time_Known_Value
(L
)
3033 and then Expr_Value
(L
) <= Expr_Value
(H
)
3037 -- Otherwise warning is warranted
3040 Error_Msg_N
("??loop range may be null", DS
);
3041 Error_Msg_N
("\??bounds may be wrong way round", DS
);
3045 -- Check if either bound is known to be outside the range of the
3046 -- loop parameter type, this is e.g. the case of a loop from
3047 -- 20..X where the type is 1..19.
3049 -- Such a loop is dubious since either it raises CE or it executes
3050 -- zero times, and that cannot be useful!
3052 if Etype
(DS
) /= Any_Type
3053 and then not Error_Posted
(DS
)
3054 and then Nkind
(DS
) = N_Subtype_Indication
3055 and then Nkind
(Constraint
(DS
)) = N_Range_Constraint
3058 LLo
: constant Node_Id
:=
3059 Low_Bound
(Range_Expression
(Constraint
(DS
)));
3060 LHi
: constant Node_Id
:=
3061 High_Bound
(Range_Expression
(Constraint
(DS
)));
3063 Bad_Bound
: Node_Id
:= Empty
;
3064 -- Suspicious loop bound
3067 -- At this stage L, H are the bounds of the type, and LLo
3068 -- Lhi are the low bound and high bound of the loop.
3070 if Compile_Time_Compare
(LLo
, L
, Assume_Valid
=> True) = LT
3072 Compile_Time_Compare
(LLo
, H
, Assume_Valid
=> True) = GT
3077 if Compile_Time_Compare
(LHi
, L
, Assume_Valid
=> True) = LT
3079 Compile_Time_Compare
(LHi
, H
, Assume_Valid
=> True) = GT
3084 if Present
(Bad_Bound
) then
3086 ("suspicious loop bound out of range of "
3087 & "loop subtype??", Bad_Bound
);
3089 ("\loop executes zero times or raises "
3090 & "Constraint_Error??", Bad_Bound
);
3095 -- This declare block is about warnings, if we get an exception while
3096 -- testing for warnings, we simply abandon the attempt silently. This
3097 -- most likely occurs as the result of a previous error, but might
3098 -- just be an obscure case we have missed. In either case, not giving
3099 -- the warning is perfectly acceptable.
3102 when others => null;
3106 -- A loop parameter cannot be effectively volatile (SPARK RM 7.1.3(4)).
3107 -- This check is relevant only when SPARK_Mode is on as it is not a
3108 -- standard Ada legality check.
3110 if SPARK_Mode
= On
and then Is_Effectively_Volatile
(Id
) then
3111 Error_Msg_N
("loop parameter cannot be volatile", Id
);
3113 end Analyze_Loop_Parameter_Specification
;
3115 ----------------------------
3116 -- Analyze_Loop_Statement --
3117 ----------------------------
3119 procedure Analyze_Loop_Statement
(N
: Node_Id
) is
3121 function Is_Container_Iterator
(Iter
: Node_Id
) return Boolean;
3122 -- Given a loop iteration scheme, determine whether it is an Ada 2012
3123 -- container iteration.
3125 function Is_Wrapped_In_Block
(N
: Node_Id
) return Boolean;
3126 -- Determine whether loop statement N has been wrapped in a block to
3127 -- capture finalization actions that may be generated for container
3128 -- iterators. Prevents infinite recursion when block is analyzed.
3129 -- Routine is a noop if loop is single statement within source block.
3131 ---------------------------
3132 -- Is_Container_Iterator --
3133 ---------------------------
3135 function Is_Container_Iterator
(Iter
: Node_Id
) return Boolean is
3144 elsif Present
(Condition
(Iter
)) then
3147 -- for Def_Id in [reverse] Name loop
3148 -- for Def_Id [: Subtype_Indication] of [reverse] Name loop
3150 elsif Present
(Iterator_Specification
(Iter
)) then
3152 Nam
: constant Node_Id
:= Name
(Iterator_Specification
(Iter
));
3156 Nam_Copy
:= New_Copy_Tree
(Nam
);
3157 Set_Parent
(Nam_Copy
, Parent
(Nam
));
3158 Preanalyze_Range
(Nam_Copy
);
3160 -- The only two options here are iteration over a container or
3163 return not Is_Array_Type
(Etype
(Nam_Copy
));
3166 -- for Def_Id in [reverse] Discrete_Subtype_Definition loop
3170 LP
: constant Node_Id
:= Loop_Parameter_Specification
(Iter
);
3171 DS
: constant Node_Id
:= Discrete_Subtype_Definition
(LP
);
3175 DS_Copy
:= New_Copy_Tree
(DS
);
3176 Set_Parent
(DS_Copy
, Parent
(DS
));
3177 Preanalyze_Range
(DS_Copy
);
3179 -- Check for a call to Iterate () or an expression with
3180 -- an iterator type.
3183 (Nkind
(DS_Copy
) = N_Function_Call
3184 and then Needs_Finalization
(Etype
(DS_Copy
)))
3185 or else Is_Iterator
(Etype
(DS_Copy
));
3188 end Is_Container_Iterator
;
3190 -------------------------
3191 -- Is_Wrapped_In_Block --
3192 -------------------------
3194 function Is_Wrapped_In_Block
(N
: Node_Id
) return Boolean is
3200 -- Check if current scope is a block that is not a transient block.
3202 if Ekind
(Current_Scope
) /= E_Block
3203 or else No
(Block_Node
(Current_Scope
))
3209 Handled_Statement_Sequence
(Parent
(Block_Node
(Current_Scope
)));
3211 -- Skip leading pragmas that may be introduced for invariant and
3212 -- predicate checks.
3214 Stat
:= First
(Statements
(HSS
));
3215 while Present
(Stat
) and then Nkind
(Stat
) = N_Pragma
loop
3216 Stat
:= Next
(Stat
);
3219 return Stat
= N
and then No
(Next
(Stat
));
3221 end Is_Wrapped_In_Block
;
3223 -- Local declarations
3225 Id
: constant Node_Id
:= Identifier
(N
);
3226 Iter
: constant Node_Id
:= Iteration_Scheme
(N
);
3227 Loc
: constant Source_Ptr
:= Sloc
(N
);
3231 -- Start of processing for Analyze_Loop_Statement
3234 if Present
(Id
) then
3236 -- Make name visible, e.g. for use in exit statements. Loop labels
3237 -- are always considered to be referenced.
3242 -- Guard against serious error (typically, a scope mismatch when
3243 -- semantic analysis is requested) by creating loop entity to
3244 -- continue analysis.
3247 if Total_Errors_Detected
/= 0 then
3248 Ent
:= New_Internal_Entity
(E_Loop
, Current_Scope
, Loc
, 'L');
3250 raise Program_Error
;
3253 -- Verify that the loop name is hot hidden by an unrelated
3254 -- declaration in an inner scope.
3256 elsif Ekind
(Ent
) /= E_Label
and then Ekind
(Ent
) /= E_Loop
then
3257 Error_Msg_Sloc
:= Sloc
(Ent
);
3258 Error_Msg_N
("implicit label declaration for & is hidden#", Id
);
3260 if Present
(Homonym
(Ent
))
3261 and then Ekind
(Homonym
(Ent
)) = E_Label
3263 Set_Entity
(Id
, Ent
);
3264 Set_Ekind
(Ent
, E_Loop
);
3268 Generate_Reference
(Ent
, N
, ' ');
3269 Generate_Definition
(Ent
);
3271 -- If we found a label, mark its type. If not, ignore it, since it
3272 -- means we have a conflicting declaration, which would already
3273 -- have been diagnosed at declaration time. Set Label_Construct
3274 -- of the implicit label declaration, which is not created by the
3275 -- parser for generic units.
3277 if Ekind
(Ent
) = E_Label
then
3278 Set_Ekind
(Ent
, E_Loop
);
3280 if Nkind
(Parent
(Ent
)) = N_Implicit_Label_Declaration
then
3281 Set_Label_Construct
(Parent
(Ent
), N
);
3286 -- Case of no identifier present. Create one and attach it to the
3287 -- loop statement for use as a scope and as a reference for later
3288 -- expansions. Indicate that the label does not come from source,
3289 -- and attach it to the loop statement so it is part of the tree,
3290 -- even without a full declaration.
3293 Ent
:= New_Internal_Entity
(E_Loop
, Current_Scope
, Loc
, 'L');
3294 Set_Etype
(Ent
, Standard_Void_Type
);
3295 Set_Identifier
(N
, New_Occurrence_Of
(Ent
, Loc
));
3296 Set_Parent
(Ent
, N
);
3297 Set_Has_Created_Identifier
(N
);
3300 -- If the iterator specification has a syntactic error, transform
3301 -- construct into an infinite loop to prevent a crash and perform
3305 and then Present
(Iterator_Specification
(Iter
))
3306 and then Error_Posted
(Iterator_Specification
(Iter
))
3308 Set_Iteration_Scheme
(N
, Empty
);
3313 -- Iteration over a container in Ada 2012 involves the creation of a
3314 -- controlled iterator object. Wrap the loop in a block to ensure the
3315 -- timely finalization of the iterator and release of container locks.
3316 -- The same applies to the use of secondary stack when obtaining an
3319 if Ada_Version
>= Ada_2012
3320 and then Is_Container_Iterator
(Iter
)
3321 and then not Is_Wrapped_In_Block
(N
)
3324 Block_Nod
: Node_Id
;
3325 Block_Id
: Entity_Id
;
3329 Make_Block_Statement
(Loc
,
3330 Declarations
=> New_List
,
3331 Handled_Statement_Sequence
=>
3332 Make_Handled_Sequence_Of_Statements
(Loc
,
3333 Statements
=> New_List
(Relocate_Node
(N
))));
3335 Add_Block_Identifier
(Block_Nod
, Block_Id
);
3337 -- The expansion of iterator loops generates an iterator in order
3338 -- to traverse the elements of a container:
3340 -- Iter : <iterator type> := Iterate (Container)'reference;
3342 -- The iterator is controlled and returned on the secondary stack.
3343 -- The analysis of the call to Iterate establishes a transient
3344 -- scope to deal with the secondary stack management, but never
3345 -- really creates a physical block as this would kill the iterator
3346 -- too early (see Wrap_Transient_Declaration). To address this
3347 -- case, mark the generated block as needing secondary stack
3350 Set_Uses_Sec_Stack
(Block_Id
);
3352 Rewrite
(N
, Block_Nod
);
3358 -- Kill current values on entry to loop, since statements in the body of
3359 -- the loop may have been executed before the loop is entered. Similarly
3360 -- we kill values after the loop, since we do not know that the body of
3361 -- the loop was executed.
3363 Kill_Current_Values
;
3365 Analyze_Iteration_Scheme
(Iter
);
3367 -- Check for following case which merits a warning if the type E of is
3368 -- a multi-dimensional array (and no explicit subscript ranges present).
3374 and then Present
(Loop_Parameter_Specification
(Iter
))
3377 LPS
: constant Node_Id
:= Loop_Parameter_Specification
(Iter
);
3378 DSD
: constant Node_Id
:=
3379 Original_Node
(Discrete_Subtype_Definition
(LPS
));
3381 if Nkind
(DSD
) = N_Attribute_Reference
3382 and then Attribute_Name
(DSD
) = Name_Range
3383 and then No
(Expressions
(DSD
))
3386 Typ
: constant Entity_Id
:= Etype
(Prefix
(DSD
));
3388 if Is_Array_Type
(Typ
)
3389 and then Number_Dimensions
(Typ
) > 1
3390 and then Nkind
(Parent
(N
)) = N_Loop_Statement
3391 and then Present
(Iteration_Scheme
(Parent
(N
)))
3394 OIter
: constant Node_Id
:=
3395 Iteration_Scheme
(Parent
(N
));
3396 OLPS
: constant Node_Id
:=
3397 Loop_Parameter_Specification
(OIter
);
3398 ODSD
: constant Node_Id
:=
3399 Original_Node
(Discrete_Subtype_Definition
(OLPS
));
3401 if Nkind
(ODSD
) = N_Attribute_Reference
3402 and then Attribute_Name
(ODSD
) = Name_Range
3403 and then No
(Expressions
(ODSD
))
3404 and then Etype
(Prefix
(ODSD
)) = Typ
3406 Error_Msg_Sloc
:= Sloc
(ODSD
);
3408 ("inner range same as outer range#??", DSD
);
3417 -- Analyze the statements of the body except in the case of an Ada 2012
3418 -- iterator with the expander active. In this case the expander will do
3419 -- a rewrite of the loop into a while loop. We will then analyze the
3420 -- loop body when we analyze this while loop.
3422 -- We need to do this delay because if the container is for indefinite
3423 -- types the actual subtype of the components will only be determined
3424 -- when the cursor declaration is analyzed.
3426 -- If the expander is not active then we want to analyze the loop body
3427 -- now even in the Ada 2012 iterator case, since the rewriting will not
3428 -- be done. Insert the loop variable in the current scope, if not done
3429 -- when analysing the iteration scheme. Set its kind properly to detect
3430 -- improper uses in the loop body.
3432 -- In GNATprove mode, we do one of the above depending on the kind of
3433 -- loop. If it is an iterator over an array, then we do not analyze the
3434 -- loop now. We will analyze it after it has been rewritten by the
3435 -- special SPARK expansion which is activated in GNATprove mode. We need
3436 -- to do this so that other expansions that should occur in GNATprove
3437 -- mode take into account the specificities of the rewritten loop, in
3438 -- particular the introduction of a renaming (which needs to be
3441 -- In other cases in GNATprove mode then we want to analyze the loop
3442 -- body now, since no rewriting will occur. Within a generic the
3443 -- GNATprove mode is irrelevant, we must analyze the generic for
3444 -- non-local name capture.
3447 and then Present
(Iterator_Specification
(Iter
))
3450 and then Is_Iterator_Over_Array
(Iterator_Specification
(Iter
))
3451 and then not Inside_A_Generic
3455 elsif not Expander_Active
then
3457 I_Spec
: constant Node_Id
:= Iterator_Specification
(Iter
);
3458 Id
: constant Entity_Id
:= Defining_Identifier
(I_Spec
);
3461 if Scope
(Id
) /= Current_Scope
then
3465 -- In an element iterator, The loop parameter is a variable if
3466 -- the domain of iteration (container or array) is a variable.
3468 if not Of_Present
(I_Spec
)
3469 or else not Is_Variable
(Name
(I_Spec
))
3471 Set_Ekind
(Id
, E_Loop_Parameter
);
3475 Analyze_Statements
(Statements
(N
));
3480 -- Pre-Ada2012 for-loops and while loops.
3482 Analyze_Statements
(Statements
(N
));
3485 -- When the iteration scheme of a loop contains attribute 'Loop_Entry,
3486 -- the loop is transformed into a conditional block. Retrieve the loop.
3490 if Subject_To_Loop_Entry_Attributes
(Stmt
) then
3491 Stmt
:= Find_Loop_In_Conditional_Block
(Stmt
);
3494 -- Finish up processing for the loop. We kill all current values, since
3495 -- in general we don't know if the statements in the loop have been
3496 -- executed. We could do a bit better than this with a loop that we
3497 -- know will execute at least once, but it's not worth the trouble and
3498 -- the front end is not in the business of flow tracing.
3500 Process_End_Label
(Stmt
, 'e', Ent
);
3502 Kill_Current_Values
;
3504 -- Check for infinite loop. Skip check for generated code, since it
3505 -- justs waste time and makes debugging the routine called harder.
3507 -- Note that we have to wait till the body of the loop is fully analyzed
3508 -- before making this call, since Check_Infinite_Loop_Warning relies on
3509 -- being able to use semantic visibility information to find references.
3511 if Comes_From_Source
(Stmt
) then
3512 Check_Infinite_Loop_Warning
(Stmt
);
3515 -- Code after loop is unreachable if the loop has no WHILE or FOR and
3516 -- contains no EXIT statements within the body of the loop.
3518 if No
(Iter
) and then not Has_Exit
(Ent
) then
3519 Check_Unreachable_Code
(Stmt
);
3521 end Analyze_Loop_Statement
;
3523 ----------------------------
3524 -- Analyze_Null_Statement --
3525 ----------------------------
3527 -- Note: the semantics of the null statement is implemented by a single
3528 -- null statement, too bad everything isn't as simple as this.
3530 procedure Analyze_Null_Statement
(N
: Node_Id
) is
3531 pragma Warnings
(Off
, N
);
3534 end Analyze_Null_Statement
;
3536 -------------------------
3537 -- Analyze_Target_Name --
3538 -------------------------
3540 procedure Analyze_Target_Name
(N
: Node_Id
) is
3542 if No
(Current_LHS
) then
3543 Error_Msg_N
("target name can only appear within an assignment", N
);
3544 Set_Etype
(N
, Any_Type
);
3547 Set_Has_Target_Names
(Parent
(Current_LHS
));
3548 Set_Etype
(N
, Etype
(Current_LHS
));
3550 -- Disable expansion for the rest of the analysis of the current
3551 -- right-hand side. The enclosing assignment statement will be
3552 -- rewritten during expansion, together with occurrences of the
3555 if Expander_Active
then
3556 Expander_Mode_Save_And_Set
(False);
3559 end Analyze_Target_Name
;
3561 ------------------------
3562 -- Analyze_Statements --
3563 ------------------------
3565 procedure Analyze_Statements
(L
: List_Id
) is
3570 -- The labels declared in the statement list are reachable from
3571 -- statements in the list. We do this as a prepass so that any goto
3572 -- statement will be properly flagged if its target is not reachable.
3573 -- This is not required, but is nice behavior.
3576 while Present
(S
) loop
3577 if Nkind
(S
) = N_Label
then
3578 Analyze
(Identifier
(S
));
3579 Lab
:= Entity
(Identifier
(S
));
3581 -- If we found a label mark it as reachable
3583 if Ekind
(Lab
) = E_Label
then
3584 Generate_Definition
(Lab
);
3585 Set_Reachable
(Lab
);
3587 if Nkind
(Parent
(Lab
)) = N_Implicit_Label_Declaration
then
3588 Set_Label_Construct
(Parent
(Lab
), S
);
3591 -- If we failed to find a label, it means the implicit declaration
3592 -- of the label was hidden. A for-loop parameter can do this to
3593 -- a label with the same name inside the loop, since the implicit
3594 -- label declaration is in the innermost enclosing body or block
3598 Error_Msg_Sloc
:= Sloc
(Lab
);
3600 ("implicit label declaration for & is hidden#",
3608 -- Perform semantic analysis on all statements
3610 Conditional_Statements_Begin
;
3613 while Present
(S
) loop
3616 -- Remove dimension in all statements
3618 Remove_Dimension_In_Statement
(S
);
3622 Conditional_Statements_End
;
3624 -- Make labels unreachable. Visibility is not sufficient, because labels
3625 -- in one if-branch for example are not reachable from the other branch,
3626 -- even though their declarations are in the enclosing declarative part.
3629 while Present
(S
) loop
3630 if Nkind
(S
) = N_Label
then
3631 Set_Reachable
(Entity
(Identifier
(S
)), False);
3636 end Analyze_Statements
;
3638 ----------------------------
3639 -- Check_Unreachable_Code --
3640 ----------------------------
3642 procedure Check_Unreachable_Code
(N
: Node_Id
) is
3643 Error_Node
: Node_Id
;
3647 if Is_List_Member
(N
) and then Comes_From_Source
(N
) then
3652 Nxt
:= Original_Node
(Next
(N
));
3654 -- Skip past pragmas
3656 while Nkind
(Nxt
) = N_Pragma
loop
3657 Nxt
:= Original_Node
(Next
(Nxt
));
3660 -- If a label follows us, then we never have dead code, since
3661 -- someone could branch to the label, so we just ignore it, unless
3662 -- we are in formal mode where goto statements are not allowed.
3664 if Nkind
(Nxt
) = N_Label
3665 and then not Restriction_Check_Required
(SPARK_05
)
3669 -- Otherwise see if we have a real statement following us
3672 and then Comes_From_Source
(Nxt
)
3673 and then Is_Statement
(Nxt
)
3675 -- Special very annoying exception. If we have a return that
3676 -- follows a raise, then we allow it without a warning, since
3677 -- the Ada RM annoyingly requires a useless return here.
3679 if Nkind
(Original_Node
(N
)) /= N_Raise_Statement
3680 or else Nkind
(Nxt
) /= N_Simple_Return_Statement
3682 -- The rather strange shenanigans with the warning message
3683 -- here reflects the fact that Kill_Dead_Code is very good
3684 -- at removing warnings in deleted code, and this is one
3685 -- warning we would prefer NOT to have removed.
3689 -- If we have unreachable code, analyze and remove the
3690 -- unreachable code, since it is useless and we don't
3691 -- want to generate junk warnings.
3693 -- We skip this step if we are not in code generation mode
3694 -- or CodePeer mode.
3696 -- This is the one case where we remove dead code in the
3697 -- semantics as opposed to the expander, and we do not want
3698 -- to remove code if we are not in code generation mode,
3699 -- since this messes up the ASIS trees or loses useful
3700 -- information in the CodePeer tree.
3702 -- Note that one might react by moving the whole circuit to
3703 -- exp_ch5, but then we lose the warning in -gnatc mode.
3705 if Operating_Mode
= Generate_Code
3706 and then not CodePeer_Mode
3711 -- Quit deleting when we have nothing more to delete
3712 -- or if we hit a label (since someone could transfer
3713 -- control to a label, so we should not delete it).
3715 exit when No
(Nxt
) or else Nkind
(Nxt
) = N_Label
;
3717 -- Statement/declaration is to be deleted
3721 Kill_Dead_Code
(Nxt
);
3725 -- Now issue the warning (or error in formal mode)
3727 if Restriction_Check_Required
(SPARK_05
) then
3728 Check_SPARK_05_Restriction
3729 ("unreachable code is not allowed", Error_Node
);
3731 Error_Msg
("??unreachable code!", Sloc
(Error_Node
));
3735 -- If the unconditional transfer of control instruction is the
3736 -- last statement of a sequence, then see if our parent is one of
3737 -- the constructs for which we count unblocked exits, and if so,
3738 -- adjust the count.
3743 -- Statements in THEN part or ELSE part of IF statement
3745 if Nkind
(P
) = N_If_Statement
then
3748 -- Statements in ELSIF part of an IF statement
3750 elsif Nkind
(P
) = N_Elsif_Part
then
3752 pragma Assert
(Nkind
(P
) = N_If_Statement
);
3754 -- Statements in CASE statement alternative
3756 elsif Nkind
(P
) = N_Case_Statement_Alternative
then
3758 pragma Assert
(Nkind
(P
) = N_Case_Statement
);
3760 -- Statements in body of block
3762 elsif Nkind
(P
) = N_Handled_Sequence_Of_Statements
3763 and then Nkind
(Parent
(P
)) = N_Block_Statement
3765 -- The original loop is now placed inside a block statement
3766 -- due to the expansion of attribute 'Loop_Entry. Return as
3767 -- this is not a "real" block for the purposes of exit
3770 if Nkind
(N
) = N_Loop_Statement
3771 and then Subject_To_Loop_Entry_Attributes
(N
)
3776 -- Statements in exception handler in a block
3778 elsif Nkind
(P
) = N_Exception_Handler
3779 and then Nkind
(Parent
(P
)) = N_Handled_Sequence_Of_Statements
3780 and then Nkind
(Parent
(Parent
(P
))) = N_Block_Statement
3784 -- None of these cases, so return
3790 -- This was one of the cases we are looking for (i.e. the
3791 -- parent construct was IF, CASE or block) so decrement count.
3793 Unblocked_Exit_Count
:= Unblocked_Exit_Count
- 1;
3797 end Check_Unreachable_Code
;
3799 ----------------------
3800 -- Preanalyze_Range --
3801 ----------------------
3803 procedure Preanalyze_Range
(R_Copy
: Node_Id
) is
3804 Save_Analysis
: constant Boolean := Full_Analysis
;
3808 Full_Analysis
:= False;
3809 Expander_Mode_Save_And_Set
(False);
3813 if Nkind
(R_Copy
) in N_Subexpr
and then Is_Overloaded
(R_Copy
) then
3815 -- Apply preference rules for range of predefined integer types, or
3816 -- diagnose true ambiguity.
3821 Found
: Entity_Id
:= Empty
;
3824 Get_First_Interp
(R_Copy
, I
, It
);
3825 while Present
(It
.Typ
) loop
3826 if Is_Discrete_Type
(It
.Typ
) then
3830 if Scope
(Found
) = Standard_Standard
then
3833 elsif Scope
(It
.Typ
) = Standard_Standard
then
3837 -- Both of them are user-defined
3840 ("ambiguous bounds in range of iteration", R_Copy
);
3841 Error_Msg_N
("\possible interpretations:", R_Copy
);
3842 Error_Msg_NE
("\\} ", R_Copy
, Found
);
3843 Error_Msg_NE
("\\} ", R_Copy
, It
.Typ
);
3849 Get_Next_Interp
(I
, It
);
3854 -- Subtype mark in iteration scheme
3856 if Is_Entity_Name
(R_Copy
) and then Is_Type
(Entity
(R_Copy
)) then
3859 -- Expression in range, or Ada 2012 iterator
3861 elsif Nkind
(R_Copy
) in N_Subexpr
then
3863 Typ
:= Etype
(R_Copy
);
3865 if Is_Discrete_Type
(Typ
) then
3868 -- Check that the resulting object is an iterable container
3870 elsif Has_Aspect
(Typ
, Aspect_Iterator_Element
)
3871 or else Has_Aspect
(Typ
, Aspect_Constant_Indexing
)
3872 or else Has_Aspect
(Typ
, Aspect_Variable_Indexing
)
3876 -- The expression may yield an implicit reference to an iterable
3877 -- container. Insert explicit dereference so that proper type is
3878 -- visible in the loop.
3880 elsif Has_Implicit_Dereference
(Etype
(R_Copy
)) then
3885 Disc
:= First_Discriminant
(Typ
);
3886 while Present
(Disc
) loop
3887 if Has_Implicit_Dereference
(Disc
) then
3888 Build_Explicit_Dereference
(R_Copy
, Disc
);
3892 Next_Discriminant
(Disc
);
3899 Expander_Mode_Restore
;
3900 Full_Analysis
:= Save_Analysis
;
3901 end Preanalyze_Range
;