[19/77] Add a smallest_int_mode_for_size helper function
[official-gcc.git] / gcc / ada / sem_ch5.adb
blob6ef90955102136e77a122678aafa8b3d816b73bf
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ C H 5 --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2017, Free Software Foundation, Inc. --
10 -- --
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. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
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;
36 with Lib; use Lib;
37 with Lib.Xref; use Lib.Xref;
38 with Namet; use Namet;
39 with Nlists; use Nlists;
40 with Nmake; use Nmake;
41 with Opt; use Opt;
42 with Restrict; use Restrict;
43 with Rident; use Rident;
44 with Sem; use Sem;
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_Assignment : Node_Id := Empty;
68 -- This variable holds the node for an assignment that contains target
69 -- names. The corresponding flag has been set by the parser, and when
70 -- set the analysis of the RHS must be done with all expansion disabled,
71 -- because the assignment is reanalyzed after expansion has replaced all
72 -- occurrences of the target name appropriately.
74 Unblocked_Exit_Count : Nat := 0;
75 -- This variable is used when processing if statements, case statements,
76 -- and block statements. It counts the number of exit points that are not
77 -- blocked by unconditional transfer instructions: for IF and CASE, these
78 -- are the branches of the conditional; for a block, they are the statement
79 -- sequence of the block, and the statement sequences of any exception
80 -- handlers that are part of the block. When processing is complete, if
81 -- this count is zero, it means that control cannot fall through the IF,
82 -- CASE or block statement. This is used for the generation of warning
83 -- messages. This variable is recursively saved on entry to processing the
84 -- construct, and restored on exit.
86 procedure Preanalyze_Range (R_Copy : Node_Id);
87 -- Determine expected type of range or domain of iteration of Ada 2012
88 -- loop by analyzing separate copy. Do the analysis and resolution of the
89 -- copy of the bound(s) with expansion disabled, to prevent the generation
90 -- of finalization actions. This prevents memory leaks when the bounds
91 -- contain calls to functions returning controlled arrays or when the
92 -- domain of iteration is a container.
94 ------------------------
95 -- Analyze_Assignment --
96 ------------------------
98 -- WARNING: This routine manages Ghost regions. Return statements must be
99 -- replaced by gotos which jump to the end of the routine and restore the
100 -- Ghost mode.
102 procedure Analyze_Assignment (N : Node_Id) is
103 Lhs : constant Node_Id := Name (N);
104 Rhs : constant Node_Id := Expression (N);
106 Decl : Node_Id;
107 T1 : Entity_Id;
108 T2 : Entity_Id;
110 Save_Full_Analysis : Boolean := False; -- initialize to prevent warning
112 procedure Diagnose_Non_Variable_Lhs (N : Node_Id);
113 -- N is the node for the left hand side of an assignment, and it is not
114 -- a variable. This routine issues an appropriate diagnostic.
116 procedure Kill_Lhs;
117 -- This is called to kill current value settings of a simple variable
118 -- on the left hand side. We call it if we find any error in analyzing
119 -- the assignment, and at the end of processing before setting any new
120 -- current values in place.
122 procedure Set_Assignment_Type
123 (Opnd : Node_Id;
124 Opnd_Type : in out Entity_Id);
125 -- Opnd is either the Lhs or Rhs of the assignment, and Opnd_Type is the
126 -- nominal subtype. This procedure is used to deal with cases where the
127 -- nominal subtype must be replaced by the actual subtype.
129 -------------------------------
130 -- Diagnose_Non_Variable_Lhs --
131 -------------------------------
133 procedure Diagnose_Non_Variable_Lhs (N : Node_Id) is
134 begin
135 -- Not worth posting another error if left hand side already flagged
136 -- as being illegal in some respect.
138 if Error_Posted (N) then
139 return;
141 -- Some special bad cases of entity names
143 elsif Is_Entity_Name (N) then
144 declare
145 Ent : constant Entity_Id := Entity (N);
147 begin
148 if Ekind (Ent) = E_In_Parameter then
149 Error_Msg_N
150 ("assignment to IN mode parameter not allowed", N);
151 return;
153 -- Renamings of protected private components are turned into
154 -- constants when compiling a protected function. In the case
155 -- of single protected types, the private component appears
156 -- directly.
158 elsif (Is_Prival (Ent)
159 and then
160 (Ekind (Current_Scope) = E_Function
161 or else Ekind (Enclosing_Dynamic_Scope
162 (Current_Scope)) = E_Function))
163 or else
164 (Ekind (Ent) = E_Component
165 and then Is_Protected_Type (Scope (Ent)))
166 then
167 Error_Msg_N
168 ("protected function cannot modify protected object", N);
169 return;
171 elsif Ekind (Ent) = E_Loop_Parameter then
172 Error_Msg_N ("assignment to loop parameter not allowed", N);
173 return;
174 end if;
175 end;
177 -- For indexed components, test prefix if it is in array. We do not
178 -- want to recurse for cases where the prefix is a pointer, since we
179 -- may get a message confusing the pointer and what it references.
181 elsif Nkind (N) = N_Indexed_Component
182 and then Is_Array_Type (Etype (Prefix (N)))
183 then
184 Diagnose_Non_Variable_Lhs (Prefix (N));
185 return;
187 -- Another special case for assignment to discriminant
189 elsif Nkind (N) = N_Selected_Component then
190 if Present (Entity (Selector_Name (N)))
191 and then Ekind (Entity (Selector_Name (N))) = E_Discriminant
192 then
193 Error_Msg_N ("assignment to discriminant not allowed", N);
194 return;
196 -- For selection from record, diagnose prefix, but note that again
197 -- we only do this for a record, not e.g. for a pointer.
199 elsif Is_Record_Type (Etype (Prefix (N))) then
200 Diagnose_Non_Variable_Lhs (Prefix (N));
201 return;
202 end if;
203 end if;
205 -- If we fall through, we have no special message to issue
207 Error_Msg_N ("left hand side of assignment must be a variable", N);
208 end Diagnose_Non_Variable_Lhs;
210 --------------
211 -- Kill_Lhs --
212 --------------
214 procedure Kill_Lhs is
215 begin
216 if Is_Entity_Name (Lhs) then
217 declare
218 Ent : constant Entity_Id := Entity (Lhs);
219 begin
220 if Present (Ent) then
221 Kill_Current_Values (Ent);
222 end if;
223 end;
224 end if;
225 end Kill_Lhs;
227 -------------------------
228 -- Set_Assignment_Type --
229 -------------------------
231 procedure Set_Assignment_Type
232 (Opnd : Node_Id;
233 Opnd_Type : in out Entity_Id)
235 begin
236 Require_Entity (Opnd);
238 -- If the assignment operand is an in-out or out parameter, then we
239 -- get the actual subtype (needed for the unconstrained case). If the
240 -- operand is the actual in an entry declaration, then within the
241 -- accept statement it is replaced with a local renaming, which may
242 -- also have an actual subtype.
244 if Is_Entity_Name (Opnd)
245 and then (Ekind (Entity (Opnd)) = E_Out_Parameter
246 or else Ekind_In (Entity (Opnd),
247 E_In_Out_Parameter,
248 E_Generic_In_Out_Parameter)
249 or else
250 (Ekind (Entity (Opnd)) = E_Variable
251 and then Nkind (Parent (Entity (Opnd))) =
252 N_Object_Renaming_Declaration
253 and then Nkind (Parent (Parent (Entity (Opnd)))) =
254 N_Accept_Statement))
255 then
256 Opnd_Type := Get_Actual_Subtype (Opnd);
258 -- If assignment operand is a component reference, then we get the
259 -- actual subtype of the component for the unconstrained case.
261 elsif Nkind_In (Opnd, N_Selected_Component, N_Explicit_Dereference)
262 and then not Is_Unchecked_Union (Opnd_Type)
263 then
264 Decl := Build_Actual_Subtype_Of_Component (Opnd_Type, Opnd);
266 if Present (Decl) then
267 Insert_Action (N, Decl);
268 Mark_Rewrite_Insertion (Decl);
269 Analyze (Decl);
270 Opnd_Type := Defining_Identifier (Decl);
271 Set_Etype (Opnd, Opnd_Type);
272 Freeze_Itype (Opnd_Type, N);
274 elsif Is_Constrained (Etype (Opnd)) then
275 Opnd_Type := Etype (Opnd);
276 end if;
278 -- For slice, use the constrained subtype created for the slice
280 elsif Nkind (Opnd) = N_Slice then
281 Opnd_Type := Etype (Opnd);
282 end if;
283 end Set_Assignment_Type;
285 -- Local variables
287 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
288 -- Save the Ghost mode to restore on exit
290 -- Start of processing for Analyze_Assignment
292 begin
293 Mark_Coextensions (N, Rhs);
295 -- Analyze the target of the assignment first in case the expression
296 -- contains references to Ghost entities. The checks that verify the
297 -- proper use of a Ghost entity need to know the enclosing context.
299 Analyze (Lhs);
301 -- An assignment statement is Ghost when the left hand side denotes a
302 -- Ghost entity. Set the mode now to ensure that any nodes generated
303 -- during analysis and expansion are properly marked as Ghost.
305 if Has_Target_Names (N) then
306 Current_Assignment := N;
307 Expander_Mode_Save_And_Set (False);
308 Save_Full_Analysis := Full_Analysis;
309 Full_Analysis := False;
310 else
311 Current_Assignment := Empty;
312 end if;
314 Mark_And_Set_Ghost_Assignment (N);
315 Analyze (Rhs);
317 -- Ensure that we never do an assignment on a variable marked as
318 -- Is_Safe_To_Reevaluate.
320 pragma Assert
321 (not Is_Entity_Name (Lhs)
322 or else Ekind (Entity (Lhs)) /= E_Variable
323 or else not Is_Safe_To_Reevaluate (Entity (Lhs)));
325 -- Start type analysis for assignment
327 T1 := Etype (Lhs);
329 -- In the most general case, both Lhs and Rhs can be overloaded, and we
330 -- must compute the intersection of the possible types on each side.
332 if Is_Overloaded (Lhs) then
333 declare
334 I : Interp_Index;
335 It : Interp;
337 begin
338 T1 := Any_Type;
339 Get_First_Interp (Lhs, I, It);
341 while Present (It.Typ) loop
343 -- An indexed component with generalized indexing is always
344 -- overloaded with the corresponding dereference. Discard the
345 -- interpretation that yields a reference type, which is not
346 -- assignable.
348 if Nkind (Lhs) = N_Indexed_Component
349 and then Present (Generalized_Indexing (Lhs))
350 and then Has_Implicit_Dereference (It.Typ)
351 then
352 null;
354 -- This may be a call to a parameterless function through an
355 -- implicit dereference, so discard interpretation as well.
357 elsif Is_Entity_Name (Lhs)
358 and then Has_Implicit_Dereference (It.Typ)
359 then
360 null;
362 elsif Has_Compatible_Type (Rhs, It.Typ) then
363 if T1 /= Any_Type then
365 -- An explicit dereference is overloaded if the prefix
366 -- is. Try to remove the ambiguity on the prefix, the
367 -- error will be posted there if the ambiguity is real.
369 if Nkind (Lhs) = N_Explicit_Dereference then
370 declare
371 PI : Interp_Index;
372 PI1 : Interp_Index := 0;
373 PIt : Interp;
374 Found : Boolean;
376 begin
377 Found := False;
378 Get_First_Interp (Prefix (Lhs), PI, PIt);
380 while Present (PIt.Typ) loop
381 if Is_Access_Type (PIt.Typ)
382 and then Has_Compatible_Type
383 (Rhs, Designated_Type (PIt.Typ))
384 then
385 if Found then
386 PIt :=
387 Disambiguate (Prefix (Lhs),
388 PI1, PI, Any_Type);
390 if PIt = No_Interp then
391 Error_Msg_N
392 ("ambiguous left-hand side in "
393 & "assignment", Lhs);
394 exit;
395 else
396 Resolve (Prefix (Lhs), PIt.Typ);
397 end if;
399 exit;
400 else
401 Found := True;
402 PI1 := PI;
403 end if;
404 end if;
406 Get_Next_Interp (PI, PIt);
407 end loop;
408 end;
410 else
411 Error_Msg_N
412 ("ambiguous left-hand side in assignment", Lhs);
413 exit;
414 end if;
415 else
416 T1 := It.Typ;
417 end if;
418 end if;
420 Get_Next_Interp (I, It);
421 end loop;
422 end;
424 if T1 = Any_Type then
425 Error_Msg_N
426 ("no valid types for left-hand side for assignment", Lhs);
427 Kill_Lhs;
428 goto Leave;
429 end if;
430 end if;
432 -- The resulting assignment type is T1, so now we will resolve the left
433 -- hand side of the assignment using this determined type.
435 Resolve (Lhs, T1);
437 -- Cases where Lhs is not a variable
439 -- Cases where Lhs is not a variable. In an instance or an inlined body
440 -- no need for further check because assignment was legal in template.
442 if In_Inlined_Body then
443 null;
445 elsif not Is_Variable (Lhs) then
447 -- Ada 2005 (AI-327): Check assignment to the attribute Priority of a
448 -- protected object.
450 declare
451 Ent : Entity_Id;
452 S : Entity_Id;
454 begin
455 if Ada_Version >= Ada_2005 then
457 -- Handle chains of renamings
459 Ent := Lhs;
460 while Nkind (Ent) in N_Has_Entity
461 and then Present (Entity (Ent))
462 and then Present (Renamed_Object (Entity (Ent)))
463 loop
464 Ent := Renamed_Object (Entity (Ent));
465 end loop;
467 if (Nkind (Ent) = N_Attribute_Reference
468 and then Attribute_Name (Ent) = Name_Priority)
470 -- Renamings of the attribute Priority applied to protected
471 -- objects have been previously expanded into calls to the
472 -- Get_Ceiling run-time subprogram.
474 or else Is_Expanded_Priority_Attribute (Ent)
475 then
476 -- The enclosing subprogram cannot be a protected function
478 S := Current_Scope;
479 while not (Is_Subprogram (S)
480 and then Convention (S) = Convention_Protected)
481 and then S /= Standard_Standard
482 loop
483 S := Scope (S);
484 end loop;
486 if Ekind (S) = E_Function
487 and then Convention (S) = Convention_Protected
488 then
489 Error_Msg_N
490 ("protected function cannot modify protected object",
491 Lhs);
492 end if;
494 -- Changes of the ceiling priority of the protected object
495 -- are only effective if the Ceiling_Locking policy is in
496 -- effect (AARM D.5.2 (5/2)).
498 if Locking_Policy /= 'C' then
499 Error_Msg_N
500 ("assignment to the attribute PRIORITY has no effect??",
501 Lhs);
502 Error_Msg_N
503 ("\since no Locking_Policy has been specified??", Lhs);
504 end if;
506 goto Leave;
507 end if;
508 end if;
509 end;
511 Diagnose_Non_Variable_Lhs (Lhs);
512 goto Leave;
514 -- Error of assigning to limited type. We do however allow this in
515 -- certain cases where the front end generates the assignments.
517 elsif Is_Limited_Type (T1)
518 and then not Assignment_OK (Lhs)
519 and then not Assignment_OK (Original_Node (Lhs))
520 then
521 -- CPP constructors can only be called in declarations
523 if Is_CPP_Constructor_Call (Rhs) then
524 Error_Msg_N ("invalid use of 'C'P'P constructor", Rhs);
525 else
526 Error_Msg_N
527 ("left hand of assignment must not be limited type", Lhs);
528 Explain_Limited_Type (T1, Lhs);
529 end if;
531 goto Leave;
533 -- A class-wide type may be a limited view. This illegal case is not
534 -- caught by previous checks.
536 elsif Ekind (T1) = E_Class_Wide_Type and then From_Limited_With (T1) then
537 Error_Msg_NE ("invalid use of limited view of&", Lhs, T1);
538 goto Leave;
540 -- Enforce RM 3.9.3 (8): the target of an assignment operation cannot be
541 -- abstract. This is only checked when the assignment Comes_From_Source,
542 -- because in some cases the expander generates such assignments (such
543 -- in the _assign operation for an abstract type).
545 elsif Is_Abstract_Type (T1) and then Comes_From_Source (N) then
546 Error_Msg_N
547 ("target of assignment operation must not be abstract", Lhs);
548 end if;
550 -- Resolution may have updated the subtype, in case the left-hand side
551 -- is a private protected component. Use the correct subtype to avoid
552 -- scoping issues in the back-end.
554 T1 := Etype (Lhs);
556 -- Ada 2005 (AI-50217, AI-326): Check wrong dereference of incomplete
557 -- type. For example:
559 -- limited with P;
560 -- package Pkg is
561 -- type Acc is access P.T;
562 -- end Pkg;
564 -- with Pkg; use Acc;
565 -- procedure Example is
566 -- A, B : Acc;
567 -- begin
568 -- A.all := B.all; -- ERROR
569 -- end Example;
571 if Nkind (Lhs) = N_Explicit_Dereference
572 and then Ekind (T1) = E_Incomplete_Type
573 then
574 Error_Msg_N ("invalid use of incomplete type", Lhs);
575 Kill_Lhs;
576 goto Leave;
577 end if;
579 -- Now we can complete the resolution of the right hand side
581 Set_Assignment_Type (Lhs, T1);
583 Resolve (Rhs, T1);
585 -- This is the point at which we check for an unset reference
587 Check_Unset_Reference (Rhs);
588 Check_Unprotected_Access (Lhs, Rhs);
590 -- Remaining steps are skipped if Rhs was syntactically in error
592 if Rhs = Error then
593 Kill_Lhs;
594 goto Leave;
595 end if;
597 T2 := Etype (Rhs);
599 if not Covers (T1, T2) then
600 Wrong_Type (Rhs, Etype (Lhs));
601 Kill_Lhs;
602 goto Leave;
603 end if;
605 -- Ada 2005 (AI-326): In case of explicit dereference of incomplete
606 -- types, use the non-limited view if available
608 if Nkind (Rhs) = N_Explicit_Dereference
609 and then Is_Tagged_Type (T2)
610 and then Has_Non_Limited_View (T2)
611 then
612 T2 := Non_Limited_View (T2);
613 end if;
615 Set_Assignment_Type (Rhs, T2);
617 if Total_Errors_Detected /= 0 then
618 if No (T1) then
619 T1 := Any_Type;
620 end if;
622 if No (T2) then
623 T2 := Any_Type;
624 end if;
625 end if;
627 if T1 = Any_Type or else T2 = Any_Type then
628 Kill_Lhs;
629 goto Leave;
630 end if;
632 -- If the rhs is class-wide or dynamically tagged, then require the lhs
633 -- to be class-wide. The case where the rhs is a dynamically tagged call
634 -- to a dispatching operation with a controlling access result is
635 -- excluded from this check, since the target has an access type (and
636 -- no tag propagation occurs in that case).
638 if (Is_Class_Wide_Type (T2)
639 or else (Is_Dynamically_Tagged (Rhs)
640 and then not Is_Access_Type (T1)))
641 and then not Is_Class_Wide_Type (T1)
642 then
643 Error_Msg_N ("dynamically tagged expression not allowed!", Rhs);
645 elsif Is_Class_Wide_Type (T1)
646 and then not Is_Class_Wide_Type (T2)
647 and then not Is_Tag_Indeterminate (Rhs)
648 and then not Is_Dynamically_Tagged (Rhs)
649 then
650 Error_Msg_N ("dynamically tagged expression required!", Rhs);
651 end if;
653 -- Propagate the tag from a class-wide target to the rhs when the rhs
654 -- is a tag-indeterminate call.
656 if Is_Tag_Indeterminate (Rhs) then
657 if Is_Class_Wide_Type (T1) then
658 Propagate_Tag (Lhs, Rhs);
660 elsif Nkind (Rhs) = N_Function_Call
661 and then Is_Entity_Name (Name (Rhs))
662 and then Is_Abstract_Subprogram (Entity (Name (Rhs)))
663 then
664 Error_Msg_N
665 ("call to abstract function must be dispatching", Name (Rhs));
667 elsif Nkind (Rhs) = N_Qualified_Expression
668 and then Nkind (Expression (Rhs)) = N_Function_Call
669 and then Is_Entity_Name (Name (Expression (Rhs)))
670 and then
671 Is_Abstract_Subprogram (Entity (Name (Expression (Rhs))))
672 then
673 Error_Msg_N
674 ("call to abstract function must be dispatching",
675 Name (Expression (Rhs)));
676 end if;
677 end if;
679 -- Ada 2005 (AI-385): When the lhs type is an anonymous access type,
680 -- apply an implicit conversion of the rhs to that type to force
681 -- appropriate static and run-time accessibility checks. This applies
682 -- as well to anonymous access-to-subprogram types that are component
683 -- subtypes or formal parameters.
685 if Ada_Version >= Ada_2005 and then Is_Access_Type (T1) then
686 if Is_Local_Anonymous_Access (T1)
687 or else Ekind (T2) = E_Anonymous_Access_Subprogram_Type
689 -- Handle assignment to an Ada 2012 stand-alone object
690 -- of an anonymous access type.
692 or else (Ekind (T1) = E_Anonymous_Access_Type
693 and then Nkind (Associated_Node_For_Itype (T1)) =
694 N_Object_Declaration)
696 then
697 Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
698 Analyze_And_Resolve (Rhs, T1);
699 end if;
700 end if;
702 -- Ada 2005 (AI-231): Assignment to not null variable
704 if Ada_Version >= Ada_2005
705 and then Can_Never_Be_Null (T1)
706 and then not Assignment_OK (Lhs)
707 then
708 -- Case where we know the right hand side is null
710 if Known_Null (Rhs) then
711 Apply_Compile_Time_Constraint_Error
712 (N => Rhs,
713 Msg =>
714 "(Ada 2005) null not allowed in null-excluding objects??",
715 Reason => CE_Null_Not_Allowed);
717 -- We still mark this as a possible modification, that's necessary
718 -- to reset Is_True_Constant, and desirable for xref purposes.
720 Note_Possible_Modification (Lhs, Sure => True);
721 goto Leave;
723 -- If we know the right hand side is non-null, then we convert to the
724 -- target type, since we don't need a run time check in that case.
726 elsif not Can_Never_Be_Null (T2) then
727 Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
728 Analyze_And_Resolve (Rhs, T1);
729 end if;
730 end if;
732 if Is_Scalar_Type (T1) then
733 Apply_Scalar_Range_Check (Rhs, Etype (Lhs));
735 -- For array types, verify that lengths match. If the right hand side
736 -- is a function call that has been inlined, the assignment has been
737 -- rewritten as a block, and the constraint check will be applied to the
738 -- assignment within the block.
740 elsif Is_Array_Type (T1)
741 and then (Nkind (Rhs) /= N_Type_Conversion
742 or else Is_Constrained (Etype (Rhs)))
743 and then (Nkind (Rhs) /= N_Function_Call
744 or else Nkind (N) /= N_Block_Statement)
745 then
746 -- Assignment verifies that the length of the Lsh and Rhs are equal,
747 -- but of course the indexes do not have to match. If the right-hand
748 -- side is a type conversion to an unconstrained type, a length check
749 -- is performed on the expression itself during expansion. In rare
750 -- cases, the redundant length check is computed on an index type
751 -- with a different representation, triggering incorrect code in the
752 -- back end.
754 Apply_Length_Check (Rhs, Etype (Lhs));
756 else
757 -- Discriminant checks are applied in the course of expansion
759 null;
760 end if;
762 -- Note: modifications of the Lhs may only be recorded after
763 -- checks have been applied.
765 Note_Possible_Modification (Lhs, Sure => True);
767 -- ??? a real accessibility check is needed when ???
769 -- Post warning for redundant assignment or variable to itself
771 if Warn_On_Redundant_Constructs
773 -- We only warn for source constructs
775 and then Comes_From_Source (N)
777 -- Where the object is the same on both sides
779 and then Same_Object (Lhs, Original_Node (Rhs))
781 -- But exclude the case where the right side was an operation that
782 -- got rewritten (e.g. JUNK + K, where K was known to be zero). We
783 -- don't want to warn in such a case, since it is reasonable to write
784 -- such expressions especially when K is defined symbolically in some
785 -- other package.
787 and then Nkind (Original_Node (Rhs)) not in N_Op
788 then
789 if Nkind (Lhs) in N_Has_Entity then
790 Error_Msg_NE -- CODEFIX
791 ("?r?useless assignment of & to itself!", N, Entity (Lhs));
792 else
793 Error_Msg_N -- CODEFIX
794 ("?r?useless assignment of object to itself!", N);
795 end if;
796 end if;
798 -- Check for non-allowed composite assignment
800 if not Support_Composite_Assign_On_Target
801 and then (Is_Array_Type (T1) or else Is_Record_Type (T1))
802 and then (not Has_Size_Clause (T1) or else Esize (T1) > 64)
803 then
804 Error_Msg_CRT ("composite assignment", N);
805 end if;
807 -- Check elaboration warning for left side if not in elab code
809 if not In_Subprogram_Or_Concurrent_Unit then
810 Check_Elab_Assign (Lhs);
811 end if;
813 -- Set Referenced_As_LHS if appropriate. We only set this flag if the
814 -- assignment is a source assignment in the extended main source unit.
815 -- We are not interested in any reference information outside this
816 -- context, or in compiler generated assignment statements.
818 if Comes_From_Source (N)
819 and then In_Extended_Main_Source_Unit (Lhs)
820 then
821 Set_Referenced_Modified (Lhs, Out_Param => False);
822 end if;
824 -- RM 7.3.2 (12/3): An assignment to a view conversion (from a type
825 -- to one of its ancestors) requires an invariant check. Apply check
826 -- only if expression comes from source, otherwise it will be applied
827 -- when value is assigned to source entity.
829 if Nkind (Lhs) = N_Type_Conversion
830 and then Has_Invariants (Etype (Expression (Lhs)))
831 and then Comes_From_Source (Expression (Lhs))
832 then
833 Insert_After (N, Make_Invariant_Call (Expression (Lhs)));
834 end if;
836 -- Final step. If left side is an entity, then we may be able to reset
837 -- the current tracked values to new safe values. We only have something
838 -- to do if the left side is an entity name, and expansion has not
839 -- modified the node into something other than an assignment, and of
840 -- course we only capture values if it is safe to do so.
842 if Is_Entity_Name (Lhs)
843 and then Nkind (N) = N_Assignment_Statement
844 then
845 declare
846 Ent : constant Entity_Id := Entity (Lhs);
848 begin
849 if Safe_To_Capture_Value (N, Ent) then
851 -- If simple variable on left side, warn if this assignment
852 -- blots out another one (rendering it useless). We only do
853 -- this for source assignments, otherwise we can generate bogus
854 -- warnings when an assignment is rewritten as another
855 -- assignment, and gets tied up with itself.
857 -- There may have been a previous reference to a component of
858 -- the variable, which in general removes the Last_Assignment
859 -- field of the variable to indicate a relevant use of the
860 -- previous assignment. However, if the assignment is to a
861 -- subcomponent the reference may not have registered, because
862 -- it is not possible to determine whether the context is an
863 -- assignment. In those cases we generate a Deferred_Reference,
864 -- to be used at the end of compilation to generate the right
865 -- kind of reference, and we suppress a potential warning for
866 -- a useless assignment, which might be premature. This may
867 -- lose a warning in rare cases, but seems preferable to a
868 -- misleading warning.
870 if Warn_On_Modified_Unread
871 and then Is_Assignable (Ent)
872 and then Comes_From_Source (N)
873 and then In_Extended_Main_Source_Unit (Ent)
874 and then not Has_Deferred_Reference (Ent)
875 then
876 Warn_On_Useless_Assignment (Ent, N);
877 end if;
879 -- If we are assigning an access type and the left side is an
880 -- entity, then make sure that the Is_Known_[Non_]Null flags
881 -- properly reflect the state of the entity after assignment.
883 if Is_Access_Type (T1) then
884 if Known_Non_Null (Rhs) then
885 Set_Is_Known_Non_Null (Ent, True);
887 elsif Known_Null (Rhs)
888 and then not Can_Never_Be_Null (Ent)
889 then
890 Set_Is_Known_Null (Ent, True);
892 else
893 Set_Is_Known_Null (Ent, False);
895 if not Can_Never_Be_Null (Ent) then
896 Set_Is_Known_Non_Null (Ent, False);
897 end if;
898 end if;
900 -- For discrete types, we may be able to set the current value
901 -- if the value is known at compile time.
903 elsif Is_Discrete_Type (T1)
904 and then Compile_Time_Known_Value (Rhs)
905 then
906 Set_Current_Value (Ent, Rhs);
907 else
908 Set_Current_Value (Ent, Empty);
909 end if;
911 -- If not safe to capture values, kill them
913 else
914 Kill_Lhs;
915 end if;
916 end;
917 end if;
919 -- If assigning to an object in whole or in part, note location of
920 -- assignment in case no one references value. We only do this for
921 -- source assignments, otherwise we can generate bogus warnings when an
922 -- assignment is rewritten as another assignment, and gets tied up with
923 -- itself.
925 declare
926 Ent : constant Entity_Id := Get_Enclosing_Object (Lhs);
927 begin
928 if Present (Ent)
929 and then Safe_To_Capture_Value (N, Ent)
930 and then Nkind (N) = N_Assignment_Statement
931 and then Warn_On_Modified_Unread
932 and then Is_Assignable (Ent)
933 and then Comes_From_Source (N)
934 and then In_Extended_Main_Source_Unit (Ent)
935 then
936 Set_Last_Assignment (Ent, Lhs);
937 end if;
938 end;
940 Analyze_Dimension (N);
942 <<Leave>>
943 Restore_Ghost_Mode (Saved_GM);
945 -- If the right-hand side contains target names, expansion has been
946 -- disabled to prevent expansion that might move target names out of
947 -- the context of the assignment statement. Restore the expander mode
948 -- now so that assignment statement can be properly expanded.
950 if Nkind (N) = N_Assignment_Statement and then Has_Target_Names (N) then
951 Expander_Mode_Restore;
952 Full_Analysis := Save_Full_Analysis;
953 end if;
954 end Analyze_Assignment;
956 -----------------------------
957 -- Analyze_Block_Statement --
958 -----------------------------
960 procedure Analyze_Block_Statement (N : Node_Id) is
961 procedure Install_Return_Entities (Scop : Entity_Id);
962 -- Install all entities of return statement scope Scop in the visibility
963 -- chain except for the return object since its entity is reused in a
964 -- renaming.
966 -----------------------------
967 -- Install_Return_Entities --
968 -----------------------------
970 procedure Install_Return_Entities (Scop : Entity_Id) is
971 Id : Entity_Id;
973 begin
974 Id := First_Entity (Scop);
975 while Present (Id) loop
977 -- Do not install the return object
979 if not Ekind_In (Id, E_Constant, E_Variable)
980 or else not Is_Return_Object (Id)
981 then
982 Install_Entity (Id);
983 end if;
985 Next_Entity (Id);
986 end loop;
987 end Install_Return_Entities;
989 -- Local constants and variables
991 Decls : constant List_Id := Declarations (N);
992 Id : constant Node_Id := Identifier (N);
993 HSS : constant Node_Id := Handled_Statement_Sequence (N);
995 Is_BIP_Return_Statement : Boolean;
997 -- Start of processing for Analyze_Block_Statement
999 begin
1000 -- In SPARK mode, we reject block statements. Note that the case of
1001 -- block statements generated by the expander is fine.
1003 if Nkind (Original_Node (N)) = N_Block_Statement then
1004 Check_SPARK_05_Restriction ("block statement is not allowed", N);
1005 end if;
1007 -- If no handled statement sequence is present, things are really messed
1008 -- up, and we just return immediately (defence against previous errors).
1010 if No (HSS) then
1011 Check_Error_Detected;
1012 return;
1013 end if;
1015 -- Detect whether the block is actually a rewritten return statement of
1016 -- a build-in-place function.
1018 Is_BIP_Return_Statement :=
1019 Present (Id)
1020 and then Present (Entity (Id))
1021 and then Ekind (Entity (Id)) = E_Return_Statement
1022 and then Is_Build_In_Place_Function
1023 (Return_Applies_To (Entity (Id)));
1025 -- Normal processing with HSS present
1027 declare
1028 EH : constant List_Id := Exception_Handlers (HSS);
1029 Ent : Entity_Id := Empty;
1030 S : Entity_Id;
1032 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1033 -- Recursively save value of this global, will be restored on exit
1035 begin
1036 -- Initialize unblocked exit count for statements of begin block
1037 -- plus one for each exception handler that is present.
1039 Unblocked_Exit_Count := 1;
1041 if Present (EH) then
1042 Unblocked_Exit_Count := Unblocked_Exit_Count + List_Length (EH);
1043 end if;
1045 -- If a label is present analyze it and mark it as referenced
1047 if Present (Id) then
1048 Analyze (Id);
1049 Ent := Entity (Id);
1051 -- An error defense. If we have an identifier, but no entity, then
1052 -- something is wrong. If previous errors, then just remove the
1053 -- identifier and continue, otherwise raise an exception.
1055 if No (Ent) then
1056 Check_Error_Detected;
1057 Set_Identifier (N, Empty);
1059 else
1060 Set_Ekind (Ent, E_Block);
1061 Generate_Reference (Ent, N, ' ');
1062 Generate_Definition (Ent);
1064 if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
1065 Set_Label_Construct (Parent (Ent), N);
1066 end if;
1067 end if;
1068 end if;
1070 -- If no entity set, create a label entity
1072 if No (Ent) then
1073 Ent := New_Internal_Entity (E_Block, Current_Scope, Sloc (N), 'B');
1074 Set_Identifier (N, New_Occurrence_Of (Ent, Sloc (N)));
1075 Set_Parent (Ent, N);
1076 end if;
1078 Set_Etype (Ent, Standard_Void_Type);
1079 Set_Block_Node (Ent, Identifier (N));
1080 Push_Scope (Ent);
1082 -- The block served as an extended return statement. Ensure that any
1083 -- entities created during the analysis and expansion of the return
1084 -- object declaration are once again visible.
1086 if Is_BIP_Return_Statement then
1087 Install_Return_Entities (Ent);
1088 end if;
1090 if Present (Decls) then
1091 Analyze_Declarations (Decls);
1092 Check_Completion;
1093 Inspect_Deferred_Constant_Completion (Decls);
1094 end if;
1096 Analyze (HSS);
1097 Process_End_Label (HSS, 'e', Ent);
1099 -- If exception handlers are present, then we indicate that enclosing
1100 -- scopes contain a block with handlers. We only need to mark non-
1101 -- generic scopes.
1103 if Present (EH) then
1104 S := Scope (Ent);
1105 loop
1106 Set_Has_Nested_Block_With_Handler (S);
1107 exit when Is_Overloadable (S)
1108 or else Ekind (S) = E_Package
1109 or else Is_Generic_Unit (S);
1110 S := Scope (S);
1111 end loop;
1112 end if;
1114 Check_References (Ent);
1115 End_Scope;
1117 if Unblocked_Exit_Count = 0 then
1118 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1119 Check_Unreachable_Code (N);
1120 else
1121 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1122 end if;
1123 end;
1124 end Analyze_Block_Statement;
1126 --------------------------------
1127 -- Analyze_Compound_Statement --
1128 --------------------------------
1130 procedure Analyze_Compound_Statement (N : Node_Id) is
1131 begin
1132 Analyze_List (Actions (N));
1133 end Analyze_Compound_Statement;
1135 ----------------------------
1136 -- Analyze_Case_Statement --
1137 ----------------------------
1139 procedure Analyze_Case_Statement (N : Node_Id) is
1140 Exp : Node_Id;
1141 Exp_Type : Entity_Id;
1142 Exp_Btype : Entity_Id;
1143 Last_Choice : Nat;
1145 Others_Present : Boolean;
1146 -- Indicates if Others was present
1148 pragma Warnings (Off, Last_Choice);
1149 -- Don't care about assigned value
1151 Statements_Analyzed : Boolean := False;
1152 -- Set True if at least some statement sequences get analyzed. If False
1153 -- on exit, means we had a serious error that prevented full analysis of
1154 -- the case statement, and as a result it is not a good idea to output
1155 -- warning messages about unreachable code.
1157 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1158 -- Recursively save value of this global, will be restored on exit
1160 procedure Non_Static_Choice_Error (Choice : Node_Id);
1161 -- Error routine invoked by the generic instantiation below when the
1162 -- case statement has a non static choice.
1164 procedure Process_Statements (Alternative : Node_Id);
1165 -- Analyzes the statements associated with a case alternative. Needed
1166 -- by instantiation below.
1168 package Analyze_Case_Choices is new
1169 Generic_Analyze_Choices
1170 (Process_Associated_Node => Process_Statements);
1171 use Analyze_Case_Choices;
1172 -- Instantiation of the generic choice analysis package
1174 package Check_Case_Choices is new
1175 Generic_Check_Choices
1176 (Process_Empty_Choice => No_OP,
1177 Process_Non_Static_Choice => Non_Static_Choice_Error,
1178 Process_Associated_Node => No_OP);
1179 use Check_Case_Choices;
1180 -- Instantiation of the generic choice processing package
1182 -----------------------------
1183 -- Non_Static_Choice_Error --
1184 -----------------------------
1186 procedure Non_Static_Choice_Error (Choice : Node_Id) is
1187 begin
1188 Flag_Non_Static_Expr
1189 ("choice given in case statement is not static!", Choice);
1190 end Non_Static_Choice_Error;
1192 ------------------------
1193 -- Process_Statements --
1194 ------------------------
1196 procedure Process_Statements (Alternative : Node_Id) is
1197 Choices : constant List_Id := Discrete_Choices (Alternative);
1198 Ent : Entity_Id;
1200 begin
1201 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1202 Statements_Analyzed := True;
1204 -- An interesting optimization. If the case statement expression
1205 -- is a simple entity, then we can set the current value within an
1206 -- alternative if the alternative has one possible value.
1208 -- case N is
1209 -- when 1 => alpha
1210 -- when 2 | 3 => beta
1211 -- when others => gamma
1213 -- Here we know that N is initially 1 within alpha, but for beta and
1214 -- gamma, we do not know anything more about the initial value.
1216 if Is_Entity_Name (Exp) then
1217 Ent := Entity (Exp);
1219 if Ekind_In (Ent, E_Variable,
1220 E_In_Out_Parameter,
1221 E_Out_Parameter)
1222 then
1223 if List_Length (Choices) = 1
1224 and then Nkind (First (Choices)) in N_Subexpr
1225 and then Compile_Time_Known_Value (First (Choices))
1226 then
1227 Set_Current_Value (Entity (Exp), First (Choices));
1228 end if;
1230 Analyze_Statements (Statements (Alternative));
1232 -- After analyzing the case, set the current value to empty
1233 -- since we won't know what it is for the next alternative
1234 -- (unless reset by this same circuit), or after the case.
1236 Set_Current_Value (Entity (Exp), Empty);
1237 return;
1238 end if;
1239 end if;
1241 -- Case where expression is not an entity name of a variable
1243 Analyze_Statements (Statements (Alternative));
1244 end Process_Statements;
1246 -- Start of processing for Analyze_Case_Statement
1248 begin
1249 Unblocked_Exit_Count := 0;
1250 Exp := Expression (N);
1251 Analyze (Exp);
1253 -- The expression must be of any discrete type. In rare cases, the
1254 -- expander constructs a case statement whose expression has a private
1255 -- type whose full view is discrete. This can happen when generating
1256 -- a stream operation for a variant type after the type is frozen,
1257 -- when the partial of view of the type of the discriminant is private.
1258 -- In that case, use the full view to analyze case alternatives.
1260 if not Is_Overloaded (Exp)
1261 and then not Comes_From_Source (N)
1262 and then Is_Private_Type (Etype (Exp))
1263 and then Present (Full_View (Etype (Exp)))
1264 and then Is_Discrete_Type (Full_View (Etype (Exp)))
1265 then
1266 Resolve (Exp, Etype (Exp));
1267 Exp_Type := Full_View (Etype (Exp));
1269 else
1270 Analyze_And_Resolve (Exp, Any_Discrete);
1271 Exp_Type := Etype (Exp);
1272 end if;
1274 Check_Unset_Reference (Exp);
1275 Exp_Btype := Base_Type (Exp_Type);
1277 -- The expression must be of a discrete type which must be determinable
1278 -- independently of the context in which the expression occurs, but
1279 -- using the fact that the expression must be of a discrete type.
1280 -- Moreover, the type this expression must not be a character literal
1281 -- (which is always ambiguous) or, for Ada-83, a generic formal type.
1283 -- If error already reported by Resolve, nothing more to do
1285 if Exp_Btype = Any_Discrete or else Exp_Btype = Any_Type then
1286 return;
1288 elsif Exp_Btype = Any_Character then
1289 Error_Msg_N
1290 ("character literal as case expression is ambiguous", Exp);
1291 return;
1293 elsif Ada_Version = Ada_83
1294 and then (Is_Generic_Type (Exp_Btype)
1295 or else Is_Generic_Type (Root_Type (Exp_Btype)))
1296 then
1297 Error_Msg_N
1298 ("(Ada 83) case expression cannot be of a generic type", Exp);
1299 return;
1300 end if;
1302 -- If the case expression is a formal object of mode in out, then treat
1303 -- it as having a nonstatic subtype by forcing use of the base type
1304 -- (which has to get passed to Check_Case_Choices below). Also use base
1305 -- type when the case expression is parenthesized.
1307 if Paren_Count (Exp) > 0
1308 or else (Is_Entity_Name (Exp)
1309 and then Ekind (Entity (Exp)) = E_Generic_In_Out_Parameter)
1310 then
1311 Exp_Type := Exp_Btype;
1312 end if;
1314 -- Call instantiated procedures to analyzwe and check discrete choices
1316 Analyze_Choices (Alternatives (N), Exp_Type);
1317 Check_Choices (N, Alternatives (N), Exp_Type, Others_Present);
1319 -- Case statement with single OTHERS alternative not allowed in SPARK
1321 if Others_Present and then List_Length (Alternatives (N)) = 1 then
1322 Check_SPARK_05_Restriction
1323 ("OTHERS as unique case alternative is not allowed", N);
1324 end if;
1326 if Exp_Type = Universal_Integer and then not Others_Present then
1327 Error_Msg_N ("case on universal integer requires OTHERS choice", Exp);
1328 end if;
1330 -- If all our exits were blocked by unconditional transfers of control,
1331 -- then the entire CASE statement acts as an unconditional transfer of
1332 -- control, so treat it like one, and check unreachable code. Skip this
1333 -- test if we had serious errors preventing any statement analysis.
1335 if Unblocked_Exit_Count = 0 and then Statements_Analyzed then
1336 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1337 Check_Unreachable_Code (N);
1338 else
1339 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1340 end if;
1342 -- If the expander is active it will detect the case of a statically
1343 -- determined single alternative and remove warnings for the case, but
1344 -- if we are not doing expansion, that circuit won't be active. Here we
1345 -- duplicate the effect of removing warnings in the same way, so that
1346 -- we will get the same set of warnings in -gnatc mode.
1348 if not Expander_Active
1349 and then Compile_Time_Known_Value (Expression (N))
1350 and then Serious_Errors_Detected = 0
1351 then
1352 declare
1353 Chosen : constant Node_Id := Find_Static_Alternative (N);
1354 Alt : Node_Id;
1356 begin
1357 Alt := First (Alternatives (N));
1358 while Present (Alt) loop
1359 if Alt /= Chosen then
1360 Remove_Warning_Messages (Statements (Alt));
1361 end if;
1363 Next (Alt);
1364 end loop;
1365 end;
1366 end if;
1367 end Analyze_Case_Statement;
1369 ----------------------------
1370 -- Analyze_Exit_Statement --
1371 ----------------------------
1373 -- If the exit includes a name, it must be the name of a currently open
1374 -- loop. Otherwise there must be an innermost open loop on the stack, to
1375 -- which the statement implicitly refers.
1377 -- Additionally, in SPARK mode:
1379 -- The exit can only name the closest enclosing loop;
1381 -- An exit with a when clause must be directly contained in a loop;
1383 -- An exit without a when clause must be directly contained in an
1384 -- if-statement with no elsif or else, which is itself directly contained
1385 -- in a loop. The exit must be the last statement in the if-statement.
1387 procedure Analyze_Exit_Statement (N : Node_Id) is
1388 Target : constant Node_Id := Name (N);
1389 Cond : constant Node_Id := Condition (N);
1390 Scope_Id : Entity_Id := Empty; -- initialize to prevent warning
1391 U_Name : Entity_Id;
1392 Kind : Entity_Kind;
1394 begin
1395 if No (Cond) then
1396 Check_Unreachable_Code (N);
1397 end if;
1399 if Present (Target) then
1400 Analyze (Target);
1401 U_Name := Entity (Target);
1403 if not In_Open_Scopes (U_Name) or else Ekind (U_Name) /= E_Loop then
1404 Error_Msg_N ("invalid loop name in exit statement", N);
1405 return;
1407 else
1408 if Has_Loop_In_Inner_Open_Scopes (U_Name) then
1409 Check_SPARK_05_Restriction
1410 ("exit label must name the closest enclosing loop", N);
1411 end if;
1413 Set_Has_Exit (U_Name);
1414 end if;
1416 else
1417 U_Name := Empty;
1418 end if;
1420 for J in reverse 0 .. Scope_Stack.Last loop
1421 Scope_Id := Scope_Stack.Table (J).Entity;
1422 Kind := Ekind (Scope_Id);
1424 if Kind = E_Loop and then (No (Target) or else Scope_Id = U_Name) then
1425 Set_Has_Exit (Scope_Id);
1426 exit;
1428 elsif Kind = E_Block
1429 or else Kind = E_Loop
1430 or else Kind = E_Return_Statement
1431 then
1432 null;
1434 else
1435 Error_Msg_N
1436 ("cannot exit from program unit or accept statement", N);
1437 return;
1438 end if;
1439 end loop;
1441 -- Verify that if present the condition is a Boolean expression
1443 if Present (Cond) then
1444 Analyze_And_Resolve (Cond, Any_Boolean);
1445 Check_Unset_Reference (Cond);
1446 end if;
1448 -- In SPARK mode, verify that the exit statement respects the SPARK
1449 -- restrictions.
1451 if Present (Cond) then
1452 if Nkind (Parent (N)) /= N_Loop_Statement then
1453 Check_SPARK_05_Restriction
1454 ("exit with when clause must be directly in loop", N);
1455 end if;
1457 else
1458 if Nkind (Parent (N)) /= N_If_Statement then
1459 if Nkind (Parent (N)) = N_Elsif_Part then
1460 Check_SPARK_05_Restriction
1461 ("exit must be in IF without ELSIF", N);
1462 else
1463 Check_SPARK_05_Restriction ("exit must be directly in IF", N);
1464 end if;
1466 elsif Nkind (Parent (Parent (N))) /= N_Loop_Statement then
1467 Check_SPARK_05_Restriction
1468 ("exit must be in IF directly in loop", N);
1470 -- First test the presence of ELSE, so that an exit in an ELSE leads
1471 -- to an error mentioning the ELSE.
1473 elsif Present (Else_Statements (Parent (N))) then
1474 Check_SPARK_05_Restriction ("exit must be in IF without ELSE", N);
1476 -- An exit in an ELSIF does not reach here, as it would have been
1477 -- detected in the case (Nkind (Parent (N)) /= N_If_Statement).
1479 elsif Present (Elsif_Parts (Parent (N))) then
1480 Check_SPARK_05_Restriction ("exit must be in IF without ELSIF", N);
1481 end if;
1482 end if;
1484 -- Chain exit statement to associated loop entity
1486 Set_Next_Exit_Statement (N, First_Exit_Statement (Scope_Id));
1487 Set_First_Exit_Statement (Scope_Id, N);
1489 -- Since the exit may take us out of a loop, any previous assignment
1490 -- statement is not useless, so clear last assignment indications. It
1491 -- is OK to keep other current values, since if the exit statement
1492 -- does not exit, then the current values are still valid.
1494 Kill_Current_Values (Last_Assignment_Only => True);
1495 end Analyze_Exit_Statement;
1497 ----------------------------
1498 -- Analyze_Goto_Statement --
1499 ----------------------------
1501 procedure Analyze_Goto_Statement (N : Node_Id) is
1502 Label : constant Node_Id := Name (N);
1503 Scope_Id : Entity_Id;
1504 Label_Scope : Entity_Id;
1505 Label_Ent : Entity_Id;
1507 begin
1508 Check_SPARK_05_Restriction ("goto statement is not allowed", N);
1510 -- Actual semantic checks
1512 Check_Unreachable_Code (N);
1513 Kill_Current_Values (Last_Assignment_Only => True);
1515 Analyze (Label);
1516 Label_Ent := Entity (Label);
1518 -- Ignore previous error
1520 if Label_Ent = Any_Id then
1521 Check_Error_Detected;
1522 return;
1524 -- We just have a label as the target of a goto
1526 elsif Ekind (Label_Ent) /= E_Label then
1527 Error_Msg_N ("target of goto statement must be a label", Label);
1528 return;
1530 -- Check that the target of the goto is reachable according to Ada
1531 -- scoping rules. Note: the special gotos we generate for optimizing
1532 -- local handling of exceptions would violate these rules, but we mark
1533 -- such gotos as analyzed when built, so this code is never entered.
1535 elsif not Reachable (Label_Ent) then
1536 Error_Msg_N ("target of goto statement is not reachable", Label);
1537 return;
1538 end if;
1540 -- Here if goto passes initial validity checks
1542 Label_Scope := Enclosing_Scope (Label_Ent);
1544 for J in reverse 0 .. Scope_Stack.Last loop
1545 Scope_Id := Scope_Stack.Table (J).Entity;
1547 if Label_Scope = Scope_Id
1548 or else not Ekind_In (Scope_Id, E_Block, E_Loop, E_Return_Statement)
1549 then
1550 if Scope_Id /= Label_Scope then
1551 Error_Msg_N
1552 ("cannot exit from program unit or accept statement", N);
1553 end if;
1555 return;
1556 end if;
1557 end loop;
1559 raise Program_Error;
1560 end Analyze_Goto_Statement;
1562 --------------------------
1563 -- Analyze_If_Statement --
1564 --------------------------
1566 -- A special complication arises in the analysis of if statements
1568 -- The expander has circuitry to completely delete code that it can tell
1569 -- will not be executed (as a result of compile time known conditions). In
1570 -- the analyzer, we ensure that code that will be deleted in this manner
1571 -- is analyzed but not expanded. This is obviously more efficient, but
1572 -- more significantly, difficulties arise if code is expanded and then
1573 -- eliminated (e.g. exception table entries disappear). Similarly, itypes
1574 -- generated in deleted code must be frozen from start, because the nodes
1575 -- on which they depend will not be available at the freeze point.
1577 procedure Analyze_If_Statement (N : Node_Id) is
1578 E : Node_Id;
1580 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1581 -- Recursively save value of this global, will be restored on exit
1583 Save_In_Deleted_Code : Boolean;
1585 Del : Boolean := False;
1586 -- This flag gets set True if a True condition has been found, which
1587 -- means that remaining ELSE/ELSIF parts are deleted.
1589 procedure Analyze_Cond_Then (Cnode : Node_Id);
1590 -- This is applied to either the N_If_Statement node itself or to an
1591 -- N_Elsif_Part node. It deals with analyzing the condition and the THEN
1592 -- statements associated with it.
1594 -----------------------
1595 -- Analyze_Cond_Then --
1596 -----------------------
1598 procedure Analyze_Cond_Then (Cnode : Node_Id) is
1599 Cond : constant Node_Id := Condition (Cnode);
1600 Tstm : constant List_Id := Then_Statements (Cnode);
1602 begin
1603 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1604 Analyze_And_Resolve (Cond, Any_Boolean);
1605 Check_Unset_Reference (Cond);
1606 Set_Current_Value_Condition (Cnode);
1608 -- If already deleting, then just analyze then statements
1610 if Del then
1611 Analyze_Statements (Tstm);
1613 -- Compile time known value, not deleting yet
1615 elsif Compile_Time_Known_Value (Cond) then
1616 Save_In_Deleted_Code := In_Deleted_Code;
1618 -- If condition is True, then analyze the THEN statements and set
1619 -- no expansion for ELSE and ELSIF parts.
1621 if Is_True (Expr_Value (Cond)) then
1622 Analyze_Statements (Tstm);
1623 Del := True;
1624 Expander_Mode_Save_And_Set (False);
1625 In_Deleted_Code := True;
1627 -- If condition is False, analyze THEN with expansion off
1629 else -- Is_False (Expr_Value (Cond))
1630 Expander_Mode_Save_And_Set (False);
1631 In_Deleted_Code := True;
1632 Analyze_Statements (Tstm);
1633 Expander_Mode_Restore;
1634 In_Deleted_Code := Save_In_Deleted_Code;
1635 end if;
1637 -- Not known at compile time, not deleting, normal analysis
1639 else
1640 Analyze_Statements (Tstm);
1641 end if;
1642 end Analyze_Cond_Then;
1644 -- Start of processing for Analyze_If_Statement
1646 begin
1647 -- Initialize exit count for else statements. If there is no else part,
1648 -- this count will stay non-zero reflecting the fact that the uncovered
1649 -- else case is an unblocked exit.
1651 Unblocked_Exit_Count := 1;
1652 Analyze_Cond_Then (N);
1654 -- Now to analyze the elsif parts if any are present
1656 if Present (Elsif_Parts (N)) then
1657 E := First (Elsif_Parts (N));
1658 while Present (E) loop
1659 Analyze_Cond_Then (E);
1660 Next (E);
1661 end loop;
1662 end if;
1664 if Present (Else_Statements (N)) then
1665 Analyze_Statements (Else_Statements (N));
1666 end if;
1668 -- If all our exits were blocked by unconditional transfers of control,
1669 -- then the entire IF statement acts as an unconditional transfer of
1670 -- control, so treat it like one, and check unreachable code.
1672 if Unblocked_Exit_Count = 0 then
1673 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1674 Check_Unreachable_Code (N);
1675 else
1676 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1677 end if;
1679 if Del then
1680 Expander_Mode_Restore;
1681 In_Deleted_Code := Save_In_Deleted_Code;
1682 end if;
1684 if not Expander_Active
1685 and then Compile_Time_Known_Value (Condition (N))
1686 and then Serious_Errors_Detected = 0
1687 then
1688 if Is_True (Expr_Value (Condition (N))) then
1689 Remove_Warning_Messages (Else_Statements (N));
1691 if Present (Elsif_Parts (N)) then
1692 E := First (Elsif_Parts (N));
1693 while Present (E) loop
1694 Remove_Warning_Messages (Then_Statements (E));
1695 Next (E);
1696 end loop;
1697 end if;
1699 else
1700 Remove_Warning_Messages (Then_Statements (N));
1701 end if;
1702 end if;
1704 -- Warn on redundant if statement that has no effect
1706 -- Note, we could also check empty ELSIF parts ???
1708 if Warn_On_Redundant_Constructs
1710 -- If statement must be from source
1712 and then Comes_From_Source (N)
1714 -- Condition must not have obvious side effect
1716 and then Has_No_Obvious_Side_Effects (Condition (N))
1718 -- No elsif parts of else part
1720 and then No (Elsif_Parts (N))
1721 and then No (Else_Statements (N))
1723 -- Then must be a single null statement
1725 and then List_Length (Then_Statements (N)) = 1
1726 then
1727 -- Go to original node, since we may have rewritten something as
1728 -- a null statement (e.g. a case we could figure the outcome of).
1730 declare
1731 T : constant Node_Id := First (Then_Statements (N));
1732 S : constant Node_Id := Original_Node (T);
1734 begin
1735 if Comes_From_Source (S) and then Nkind (S) = N_Null_Statement then
1736 Error_Msg_N ("if statement has no effect?r?", N);
1737 end if;
1738 end;
1739 end if;
1740 end Analyze_If_Statement;
1742 ----------------------------------------
1743 -- Analyze_Implicit_Label_Declaration --
1744 ----------------------------------------
1746 -- An implicit label declaration is generated in the innermost enclosing
1747 -- declarative part. This is done for labels, and block and loop names.
1749 -- Note: any changes in this routine may need to be reflected in
1750 -- Analyze_Label_Entity.
1752 procedure Analyze_Implicit_Label_Declaration (N : Node_Id) is
1753 Id : constant Node_Id := Defining_Identifier (N);
1754 begin
1755 Enter_Name (Id);
1756 Set_Ekind (Id, E_Label);
1757 Set_Etype (Id, Standard_Void_Type);
1758 Set_Enclosing_Scope (Id, Current_Scope);
1759 end Analyze_Implicit_Label_Declaration;
1761 ------------------------------
1762 -- Analyze_Iteration_Scheme --
1763 ------------------------------
1765 procedure Analyze_Iteration_Scheme (N : Node_Id) is
1766 Cond : Node_Id;
1767 Iter_Spec : Node_Id;
1768 Loop_Spec : Node_Id;
1770 begin
1771 -- For an infinite loop, there is no iteration scheme
1773 if No (N) then
1774 return;
1775 end if;
1777 Cond := Condition (N);
1778 Iter_Spec := Iterator_Specification (N);
1779 Loop_Spec := Loop_Parameter_Specification (N);
1781 if Present (Cond) then
1782 Analyze_And_Resolve (Cond, Any_Boolean);
1783 Check_Unset_Reference (Cond);
1784 Set_Current_Value_Condition (N);
1786 elsif Present (Iter_Spec) then
1787 Analyze_Iterator_Specification (Iter_Spec);
1789 else
1790 Analyze_Loop_Parameter_Specification (Loop_Spec);
1791 end if;
1792 end Analyze_Iteration_Scheme;
1794 ------------------------------------
1795 -- Analyze_Iterator_Specification --
1796 ------------------------------------
1798 procedure Analyze_Iterator_Specification (N : Node_Id) is
1799 procedure Check_Reverse_Iteration (Typ : Entity_Id);
1800 -- For an iteration over a container, if the loop carries the Reverse
1801 -- indicator, verify that the container type has an Iterate aspect that
1802 -- implements the reversible iterator interface.
1804 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id;
1805 -- For containers with Iterator and related aspects, the cursor is
1806 -- obtained by locating an entity with the proper name in the scope
1807 -- of the type.
1809 -----------------------------
1810 -- Check_Reverse_Iteration --
1811 -----------------------------
1813 procedure Check_Reverse_Iteration (Typ : Entity_Id) is
1814 begin
1815 if Reverse_Present (N)
1816 and then not Is_Array_Type (Typ)
1817 and then not Is_Reversible_Iterator (Typ)
1818 then
1819 Error_Msg_NE
1820 ("container type does not support reverse iteration", N, Typ);
1821 end if;
1822 end Check_Reverse_Iteration;
1824 ---------------------
1825 -- Get_Cursor_Type --
1826 ---------------------
1828 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id is
1829 Ent : Entity_Id;
1831 begin
1832 -- If iterator type is derived, the cursor is declared in the scope
1833 -- of the parent type.
1835 if Is_Derived_Type (Typ) then
1836 Ent := First_Entity (Scope (Etype (Typ)));
1837 else
1838 Ent := First_Entity (Scope (Typ));
1839 end if;
1841 while Present (Ent) loop
1842 exit when Chars (Ent) = Name_Cursor;
1843 Next_Entity (Ent);
1844 end loop;
1846 if No (Ent) then
1847 return Any_Type;
1848 end if;
1850 -- The cursor is the target of generated assignments in the
1851 -- loop, and cannot have a limited type.
1853 if Is_Limited_Type (Etype (Ent)) then
1854 Error_Msg_N ("cursor type cannot be limited", N);
1855 end if;
1857 return Etype (Ent);
1858 end Get_Cursor_Type;
1860 -- Local variables
1862 Def_Id : constant Node_Id := Defining_Identifier (N);
1863 Iter_Name : constant Node_Id := Name (N);
1864 Loc : constant Source_Ptr := Sloc (N);
1865 Subt : constant Node_Id := Subtype_Indication (N);
1867 Bas : Entity_Id := Empty; -- initialize to prevent warning
1868 Typ : Entity_Id;
1870 -- Start of processing for Analyze_Iterator_Specification
1872 begin
1873 Enter_Name (Def_Id);
1875 -- AI12-0151 specifies that when the subtype indication is present, it
1876 -- must statically match the type of the array or container element.
1877 -- To simplify this check, we introduce a subtype declaration with the
1878 -- given subtype indication when it carries a constraint, and rewrite
1879 -- the original as a reference to the created subtype entity.
1881 if Present (Subt) then
1882 if Nkind (Subt) = N_Subtype_Indication then
1883 declare
1884 S : constant Entity_Id := Make_Temporary (Sloc (Subt), 'S');
1885 Decl : constant Node_Id :=
1886 Make_Subtype_Declaration (Loc,
1887 Defining_Identifier => S,
1888 Subtype_Indication => New_Copy_Tree (Subt));
1889 begin
1890 Insert_Before (Parent (Parent (N)), Decl);
1891 Analyze (Decl);
1892 Rewrite (Subt, New_Occurrence_Of (S, Sloc (Subt)));
1893 end;
1894 else
1895 Analyze (Subt);
1896 end if;
1898 -- Save entity of subtype indication for subsequent check
1900 Bas := Entity (Subt);
1901 end if;
1903 Preanalyze_Range (Iter_Name);
1905 -- Set the kind of the loop variable, which is not visible within
1906 -- the iterator name.
1908 Set_Ekind (Def_Id, E_Variable);
1910 -- Provide a link between the iterator variable and the container, for
1911 -- subsequent use in cross-reference and modification information.
1913 if Of_Present (N) then
1914 Set_Related_Expression (Def_Id, Iter_Name);
1916 -- For a container, the iterator is specified through the aspect
1918 if not Is_Array_Type (Etype (Iter_Name)) then
1919 declare
1920 Iterator : constant Entity_Id :=
1921 Find_Value_Of_Aspect
1922 (Etype (Iter_Name), Aspect_Default_Iterator);
1924 I : Interp_Index;
1925 It : Interp;
1927 begin
1928 if No (Iterator) then
1929 null; -- error reported below.
1931 elsif not Is_Overloaded (Iterator) then
1932 Check_Reverse_Iteration (Etype (Iterator));
1934 -- If Iterator is overloaded, use reversible iterator if
1935 -- one is available.
1937 elsif Is_Overloaded (Iterator) then
1938 Get_First_Interp (Iterator, I, It);
1939 while Present (It.Nam) loop
1940 if Ekind (It.Nam) = E_Function
1941 and then Is_Reversible_Iterator (Etype (It.Nam))
1942 then
1943 Set_Etype (Iterator, It.Typ);
1944 Set_Entity (Iterator, It.Nam);
1945 exit;
1946 end if;
1948 Get_Next_Interp (I, It);
1949 end loop;
1951 Check_Reverse_Iteration (Etype (Iterator));
1952 end if;
1953 end;
1954 end if;
1955 end if;
1957 -- If the domain of iteration is an expression, create a declaration for
1958 -- it, so that finalization actions are introduced outside of the loop.
1959 -- The declaration must be a renaming because the body of the loop may
1960 -- assign to elements.
1962 if not Is_Entity_Name (Iter_Name)
1964 -- When the context is a quantified expression, the renaming
1965 -- declaration is delayed until the expansion phase if we are
1966 -- doing expansion.
1968 and then (Nkind (Parent (N)) /= N_Quantified_Expression
1969 or else Operating_Mode = Check_Semantics)
1971 -- Do not perform this expansion for ASIS and when expansion is
1972 -- disabled, where the temporary may hide the transformation of a
1973 -- selected component into a prefixed function call, and references
1974 -- need to see the original expression.
1976 and then Expander_Active
1977 then
1978 declare
1979 Id : constant Entity_Id := Make_Temporary (Loc, 'R', Iter_Name);
1980 Decl : Node_Id;
1981 Act_S : Node_Id;
1983 begin
1985 -- If the domain of iteration is an array component that depends
1986 -- on a discriminant, create actual subtype for it. Pre-analysis
1987 -- does not generate the actual subtype of a selected component.
1989 if Nkind (Iter_Name) = N_Selected_Component
1990 and then Is_Array_Type (Etype (Iter_Name))
1991 then
1992 Act_S :=
1993 Build_Actual_Subtype_Of_Component
1994 (Etype (Selector_Name (Iter_Name)), Iter_Name);
1995 Insert_Action (N, Act_S);
1997 if Present (Act_S) then
1998 Typ := Defining_Identifier (Act_S);
1999 else
2000 Typ := Etype (Iter_Name);
2001 end if;
2003 else
2004 Typ := Etype (Iter_Name);
2006 -- Verify that the expression produces an iterator
2008 if not Of_Present (N) and then not Is_Iterator (Typ)
2009 and then not Is_Array_Type (Typ)
2010 and then No (Find_Aspect (Typ, Aspect_Iterable))
2011 then
2012 Error_Msg_N
2013 ("expect object that implements iterator interface",
2014 Iter_Name);
2015 end if;
2016 end if;
2018 -- Protect against malformed iterator
2020 if Typ = Any_Type then
2021 Error_Msg_N ("invalid expression in loop iterator", Iter_Name);
2022 return;
2023 end if;
2025 if not Of_Present (N) then
2026 Check_Reverse_Iteration (Typ);
2027 end if;
2029 -- The name in the renaming declaration may be a function call.
2030 -- Indicate that it does not come from source, to suppress
2031 -- spurious warnings on renamings of parameterless functions,
2032 -- a common enough idiom in user-defined iterators.
2034 Decl :=
2035 Make_Object_Renaming_Declaration (Loc,
2036 Defining_Identifier => Id,
2037 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
2038 Name =>
2039 New_Copy_Tree (Iter_Name, New_Sloc => Loc));
2041 Insert_Actions (Parent (Parent (N)), New_List (Decl));
2042 Rewrite (Name (N), New_Occurrence_Of (Id, Loc));
2043 Set_Etype (Id, Typ);
2044 Set_Etype (Name (N), Typ);
2045 end;
2047 -- Container is an entity or an array with uncontrolled components, or
2048 -- else it is a container iterator given by a function call, typically
2049 -- called Iterate in the case of predefined containers, even though
2050 -- Iterate is not a reserved name. What matters is that the return type
2051 -- of the function is an iterator type.
2053 elsif Is_Entity_Name (Iter_Name) then
2054 Analyze (Iter_Name);
2056 if Nkind (Iter_Name) = N_Function_Call then
2057 declare
2058 C : constant Node_Id := Name (Iter_Name);
2059 I : Interp_Index;
2060 It : Interp;
2062 begin
2063 if not Is_Overloaded (Iter_Name) then
2064 Resolve (Iter_Name, Etype (C));
2066 else
2067 Get_First_Interp (C, I, It);
2068 while It.Typ /= Empty loop
2069 if Reverse_Present (N) then
2070 if Is_Reversible_Iterator (It.Typ) then
2071 Resolve (Iter_Name, It.Typ);
2072 exit;
2073 end if;
2075 elsif Is_Iterator (It.Typ) then
2076 Resolve (Iter_Name, It.Typ);
2077 exit;
2078 end if;
2080 Get_Next_Interp (I, It);
2081 end loop;
2082 end if;
2083 end;
2085 -- Domain of iteration is not overloaded
2087 else
2088 Resolve (Iter_Name, Etype (Iter_Name));
2089 end if;
2091 if not Of_Present (N) then
2092 Check_Reverse_Iteration (Etype (Iter_Name));
2093 end if;
2094 end if;
2096 -- Get base type of container, for proper retrieval of Cursor type
2097 -- and primitive operations.
2099 Typ := Base_Type (Etype (Iter_Name));
2101 if Is_Array_Type (Typ) then
2102 if Of_Present (N) then
2103 Set_Etype (Def_Id, Component_Type (Typ));
2105 -- The loop variable is aliased if the array components are
2106 -- aliased.
2108 Set_Is_Aliased (Def_Id, Has_Aliased_Components (Typ));
2110 -- AI12-0047 stipulates that the domain (array or container)
2111 -- cannot be a component that depends on a discriminant if the
2112 -- enclosing object is mutable, to prevent a modification of the
2113 -- dowmain of iteration in the course of an iteration.
2115 -- If the object is an expression it has been captured in a
2116 -- temporary, so examine original node.
2118 if Nkind (Original_Node (Iter_Name)) = N_Selected_Component
2119 and then Is_Dependent_Component_Of_Mutable_Object
2120 (Original_Node (Iter_Name))
2121 then
2122 Error_Msg_N
2123 ("iterable name cannot be a discriminant-dependent "
2124 & "component of a mutable object", N);
2125 end if;
2127 if Present (Subt)
2128 and then
2129 (Base_Type (Bas) /= Base_Type (Component_Type (Typ))
2130 or else
2131 not Subtypes_Statically_Match (Bas, Component_Type (Typ)))
2132 then
2133 Error_Msg_N
2134 ("subtype indication does not match component type", Subt);
2135 end if;
2137 -- Here we have a missing Range attribute
2139 else
2140 Error_Msg_N
2141 ("missing Range attribute in iteration over an array", N);
2143 -- In Ada 2012 mode, this may be an attempt at an iterator
2145 if Ada_Version >= Ada_2012 then
2146 Error_Msg_NE
2147 ("\if& is meant to designate an element of the array, use OF",
2148 N, Def_Id);
2149 end if;
2151 -- Prevent cascaded errors
2153 Set_Ekind (Def_Id, E_Loop_Parameter);
2154 Set_Etype (Def_Id, Etype (First_Index (Typ)));
2155 end if;
2157 -- Check for type error in iterator
2159 elsif Typ = Any_Type then
2160 return;
2162 -- Iteration over a container
2164 else
2165 Set_Ekind (Def_Id, E_Loop_Parameter);
2166 Error_Msg_Ada_2012_Feature ("container iterator", Sloc (N));
2168 -- OF present
2170 if Of_Present (N) then
2171 if Has_Aspect (Typ, Aspect_Iterable) then
2172 declare
2173 Elt : constant Entity_Id :=
2174 Get_Iterable_Type_Primitive (Typ, Name_Element);
2175 begin
2176 if No (Elt) then
2177 Error_Msg_N
2178 ("missing Element primitive for iteration", N);
2179 else
2180 Set_Etype (Def_Id, Etype (Elt));
2181 end if;
2182 end;
2184 -- For a predefined container, The type of the loop variable is
2185 -- the Iterator_Element aspect of the container type.
2187 else
2188 declare
2189 Element : constant Entity_Id :=
2190 Find_Value_Of_Aspect
2191 (Typ, Aspect_Iterator_Element);
2192 Iterator : constant Entity_Id :=
2193 Find_Value_Of_Aspect
2194 (Typ, Aspect_Default_Iterator);
2195 Orig_Iter_Name : constant Node_Id :=
2196 Original_Node (Iter_Name);
2197 Cursor_Type : Entity_Id;
2199 begin
2200 if No (Element) then
2201 Error_Msg_NE ("cannot iterate over&", N, Typ);
2202 return;
2204 else
2205 Set_Etype (Def_Id, Entity (Element));
2206 Cursor_Type := Get_Cursor_Type (Typ);
2207 pragma Assert (Present (Cursor_Type));
2209 -- If subtype indication was given, verify that it covers
2210 -- the element type of the container.
2212 if Present (Subt)
2213 and then (not Covers (Bas, Etype (Def_Id))
2214 or else not Subtypes_Statically_Match
2215 (Bas, Etype (Def_Id)))
2216 then
2217 Error_Msg_N
2218 ("subtype indication does not match element type",
2219 Subt);
2220 end if;
2222 -- If the container has a variable indexing aspect, the
2223 -- element is a variable and is modifiable in the loop.
2225 if Has_Aspect (Typ, Aspect_Variable_Indexing) then
2226 Set_Ekind (Def_Id, E_Variable);
2227 end if;
2229 -- If the container is a constant, iterating over it
2230 -- requires a Constant_Indexing operation.
2232 if not Is_Variable (Iter_Name)
2233 and then not Has_Aspect (Typ, Aspect_Constant_Indexing)
2234 then
2235 Error_Msg_N
2236 ("iteration over constant container require "
2237 & "constant_indexing aspect", N);
2239 -- The Iterate function may have an in_out parameter,
2240 -- and a constant container is thus illegal.
2242 elsif Present (Iterator)
2243 and then Ekind (Entity (Iterator)) = E_Function
2244 and then Ekind (First_Formal (Entity (Iterator))) /=
2245 E_In_Parameter
2246 and then not Is_Variable (Iter_Name)
2247 then
2248 Error_Msg_N ("variable container expected", N);
2249 end if;
2251 -- Detect a case where the iterator denotes a component
2252 -- of a mutable object which depends on a discriminant.
2253 -- Note that the iterator may denote a function call in
2254 -- qualified form, in which case this check should not
2255 -- be performed.
2257 if Nkind (Orig_Iter_Name) = N_Selected_Component
2258 and then
2259 Present (Entity (Selector_Name (Orig_Iter_Name)))
2260 and then Ekind_In
2261 (Entity (Selector_Name (Orig_Iter_Name)),
2262 E_Component,
2263 E_Discriminant)
2264 and then Is_Dependent_Component_Of_Mutable_Object
2265 (Orig_Iter_Name)
2266 then
2267 Error_Msg_N
2268 ("container cannot be a discriminant-dependent "
2269 & "component of a mutable object", N);
2270 end if;
2271 end if;
2272 end;
2273 end if;
2275 -- IN iterator, domain is a range, or a call to Iterate function
2277 else
2278 -- For an iteration of the form IN, the name must denote an
2279 -- iterator, typically the result of a call to Iterate. Give a
2280 -- useful error message when the name is a container by itself.
2282 -- The type may be a formal container type, which has to have
2283 -- an Iterable aspect detailing the required primitives.
2285 if Is_Entity_Name (Original_Node (Name (N)))
2286 and then not Is_Iterator (Typ)
2287 then
2288 if Has_Aspect (Typ, Aspect_Iterable) then
2289 null;
2291 elsif not Has_Aspect (Typ, Aspect_Iterator_Element) then
2292 Error_Msg_NE
2293 ("cannot iterate over&", Name (N), Typ);
2294 else
2295 Error_Msg_N
2296 ("name must be an iterator, not a container", Name (N));
2297 end if;
2299 if Has_Aspect (Typ, Aspect_Iterable) then
2300 null;
2301 else
2302 Error_Msg_NE
2303 ("\to iterate directly over the elements of a container, "
2304 & "write `of &`", Name (N), Original_Node (Name (N)));
2306 -- No point in continuing analysis of iterator spec
2308 return;
2309 end if;
2310 end if;
2312 -- If the name is a call (typically prefixed) to some Iterate
2313 -- function, it has been rewritten as an object declaration.
2314 -- If that object is a selected component, verify that it is not
2315 -- a component of an unconstrained mutable object.
2317 if Nkind (Iter_Name) = N_Identifier
2318 or else (not Expander_Active and Comes_From_Source (Iter_Name))
2319 then
2320 declare
2321 Orig_Node : constant Node_Id := Original_Node (Iter_Name);
2322 Iter_Kind : constant Node_Kind := Nkind (Orig_Node);
2323 Obj : Node_Id;
2325 begin
2326 if Iter_Kind = N_Selected_Component then
2327 Obj := Prefix (Orig_Node);
2329 elsif Iter_Kind = N_Function_Call then
2330 Obj := First_Actual (Orig_Node);
2332 -- If neither, the name comes from source
2334 else
2335 Obj := Iter_Name;
2336 end if;
2338 if Nkind (Obj) = N_Selected_Component
2339 and then Is_Dependent_Component_Of_Mutable_Object (Obj)
2340 then
2341 Error_Msg_N
2342 ("container cannot be a discriminant-dependent "
2343 & "component of a mutable object", N);
2344 end if;
2345 end;
2346 end if;
2348 -- The result type of Iterate function is the classwide type of
2349 -- the interface parent. We need the specific Cursor type defined
2350 -- in the container package. We obtain it by name for a predefined
2351 -- container, or through the Iterable aspect for a formal one.
2353 if Has_Aspect (Typ, Aspect_Iterable) then
2354 Set_Etype (Def_Id,
2355 Get_Cursor_Type
2356 (Parent (Find_Value_Of_Aspect (Typ, Aspect_Iterable)),
2357 Typ));
2359 else
2360 Set_Etype (Def_Id, Get_Cursor_Type (Typ));
2361 Check_Reverse_Iteration (Etype (Iter_Name));
2362 end if;
2364 end if;
2365 end if;
2366 end Analyze_Iterator_Specification;
2368 -------------------
2369 -- Analyze_Label --
2370 -------------------
2372 -- Note: the semantic work required for analyzing labels (setting them as
2373 -- reachable) was done in a prepass through the statements in the block,
2374 -- so that forward gotos would be properly handled. See Analyze_Statements
2375 -- for further details. The only processing required here is to deal with
2376 -- optimizations that depend on an assumption of sequential control flow,
2377 -- since of course the occurrence of a label breaks this assumption.
2379 procedure Analyze_Label (N : Node_Id) is
2380 pragma Warnings (Off, N);
2381 begin
2382 Kill_Current_Values;
2383 end Analyze_Label;
2385 --------------------------
2386 -- Analyze_Label_Entity --
2387 --------------------------
2389 procedure Analyze_Label_Entity (E : Entity_Id) is
2390 begin
2391 Set_Ekind (E, E_Label);
2392 Set_Etype (E, Standard_Void_Type);
2393 Set_Enclosing_Scope (E, Current_Scope);
2394 Set_Reachable (E, True);
2395 end Analyze_Label_Entity;
2397 ------------------------------------------
2398 -- Analyze_Loop_Parameter_Specification --
2399 ------------------------------------------
2401 procedure Analyze_Loop_Parameter_Specification (N : Node_Id) is
2402 Loop_Nod : constant Node_Id := Parent (Parent (N));
2404 procedure Check_Controlled_Array_Attribute (DS : Node_Id);
2405 -- If the bounds are given by a 'Range reference on a function call
2406 -- that returns a controlled array, introduce an explicit declaration
2407 -- to capture the bounds, so that the function result can be finalized
2408 -- in timely fashion.
2410 procedure Check_Predicate_Use (T : Entity_Id);
2411 -- Diagnose Attempt to iterate through non-static predicate. Note that
2412 -- a type with inherited predicates may have both static and dynamic
2413 -- forms. In this case it is not sufficent to check the static predicate
2414 -- function only, look for a dynamic predicate aspect as well.
2416 function Has_Call_Using_Secondary_Stack (N : Node_Id) return Boolean;
2417 -- N is the node for an arbitrary construct. This function searches the
2418 -- construct N to see if any expressions within it contain function
2419 -- calls that use the secondary stack, returning True if any such call
2420 -- is found, and False otherwise.
2422 procedure Process_Bounds (R : Node_Id);
2423 -- If the iteration is given by a range, create temporaries and
2424 -- assignment statements block to capture the bounds and perform
2425 -- required finalization actions in case a bound includes a function
2426 -- call that uses the temporary stack. We first pre-analyze a copy of
2427 -- the range in order to determine the expected type, and analyze and
2428 -- resolve the original bounds.
2430 --------------------------------------
2431 -- Check_Controlled_Array_Attribute --
2432 --------------------------------------
2434 procedure Check_Controlled_Array_Attribute (DS : Node_Id) is
2435 begin
2436 if Nkind (DS) = N_Attribute_Reference
2437 and then Is_Entity_Name (Prefix (DS))
2438 and then Ekind (Entity (Prefix (DS))) = E_Function
2439 and then Is_Array_Type (Etype (Entity (Prefix (DS))))
2440 and then
2441 Is_Controlled (Component_Type (Etype (Entity (Prefix (DS)))))
2442 and then Expander_Active
2443 then
2444 declare
2445 Loc : constant Source_Ptr := Sloc (N);
2446 Arr : constant Entity_Id := Etype (Entity (Prefix (DS)));
2447 Indx : constant Entity_Id :=
2448 Base_Type (Etype (First_Index (Arr)));
2449 Subt : constant Entity_Id := Make_Temporary (Loc, 'S');
2450 Decl : Node_Id;
2452 begin
2453 Decl :=
2454 Make_Subtype_Declaration (Loc,
2455 Defining_Identifier => Subt,
2456 Subtype_Indication =>
2457 Make_Subtype_Indication (Loc,
2458 Subtype_Mark => New_Occurrence_Of (Indx, Loc),
2459 Constraint =>
2460 Make_Range_Constraint (Loc, Relocate_Node (DS))));
2461 Insert_Before (Loop_Nod, Decl);
2462 Analyze (Decl);
2464 Rewrite (DS,
2465 Make_Attribute_Reference (Loc,
2466 Prefix => New_Occurrence_Of (Subt, Loc),
2467 Attribute_Name => Attribute_Name (DS)));
2469 Analyze (DS);
2470 end;
2471 end if;
2472 end Check_Controlled_Array_Attribute;
2474 -------------------------
2475 -- Check_Predicate_Use --
2476 -------------------------
2478 procedure Check_Predicate_Use (T : Entity_Id) is
2479 begin
2480 -- A predicated subtype is illegal in loops and related constructs
2481 -- if the predicate is not static, or if it is a non-static subtype
2482 -- of a statically predicated subtype.
2484 if Is_Discrete_Type (T)
2485 and then Has_Predicates (T)
2486 and then (not Has_Static_Predicate (T)
2487 or else not Is_Static_Subtype (T)
2488 or else Has_Dynamic_Predicate_Aspect (T))
2489 then
2490 -- Seems a confusing message for the case of a static predicate
2491 -- with a non-static subtype???
2493 Bad_Predicated_Subtype_Use
2494 ("cannot use subtype& with non-static predicate for loop "
2495 & "iteration", Discrete_Subtype_Definition (N),
2496 T, Suggest_Static => True);
2498 elsif Inside_A_Generic and then Is_Generic_Formal (T) then
2499 Set_No_Dynamic_Predicate_On_Actual (T);
2500 end if;
2501 end Check_Predicate_Use;
2503 ------------------------------------
2504 -- Has_Call_Using_Secondary_Stack --
2505 ------------------------------------
2507 function Has_Call_Using_Secondary_Stack (N : Node_Id) return Boolean is
2509 function Check_Call (N : Node_Id) return Traverse_Result;
2510 -- Check if N is a function call which uses the secondary stack
2512 ----------------
2513 -- Check_Call --
2514 ----------------
2516 function Check_Call (N : Node_Id) return Traverse_Result is
2517 Nam : Node_Id;
2518 Subp : Entity_Id;
2519 Return_Typ : Entity_Id;
2521 begin
2522 if Nkind (N) = N_Function_Call then
2523 Nam := Name (N);
2525 -- Call using access to subprogram with explicit dereference
2527 if Nkind (Nam) = N_Explicit_Dereference then
2528 Subp := Etype (Nam);
2530 -- Call using a selected component notation or Ada 2005 object
2531 -- operation notation
2533 elsif Nkind (Nam) = N_Selected_Component then
2534 Subp := Entity (Selector_Name (Nam));
2536 -- Common case
2538 else
2539 Subp := Entity (Nam);
2540 end if;
2542 Return_Typ := Etype (Subp);
2544 if Is_Composite_Type (Return_Typ)
2545 and then not Is_Constrained (Return_Typ)
2546 then
2547 return Abandon;
2549 elsif Sec_Stack_Needed_For_Return (Subp) then
2550 return Abandon;
2551 end if;
2552 end if;
2554 -- Continue traversing the tree
2556 return OK;
2557 end Check_Call;
2559 function Check_Calls is new Traverse_Func (Check_Call);
2561 -- Start of processing for Has_Call_Using_Secondary_Stack
2563 begin
2564 return Check_Calls (N) = Abandon;
2565 end Has_Call_Using_Secondary_Stack;
2567 --------------------
2568 -- Process_Bounds --
2569 --------------------
2571 procedure Process_Bounds (R : Node_Id) is
2572 Loc : constant Source_Ptr := Sloc (N);
2574 function One_Bound
2575 (Original_Bound : Node_Id;
2576 Analyzed_Bound : Node_Id;
2577 Typ : Entity_Id) return Node_Id;
2578 -- Capture value of bound and return captured value
2580 ---------------
2581 -- One_Bound --
2582 ---------------
2584 function One_Bound
2585 (Original_Bound : Node_Id;
2586 Analyzed_Bound : Node_Id;
2587 Typ : Entity_Id) return Node_Id
2589 Assign : Node_Id;
2590 Decl : Node_Id;
2591 Id : Entity_Id;
2593 begin
2594 -- If the bound is a constant or an object, no need for a separate
2595 -- declaration. If the bound is the result of previous expansion
2596 -- it is already analyzed and should not be modified. Note that
2597 -- the Bound will be resolved later, if needed, as part of the
2598 -- call to Make_Index (literal bounds may need to be resolved to
2599 -- type Integer).
2601 if Analyzed (Original_Bound) then
2602 return Original_Bound;
2604 elsif Nkind_In (Analyzed_Bound, N_Integer_Literal,
2605 N_Character_Literal)
2606 or else Is_Entity_Name (Analyzed_Bound)
2607 then
2608 Analyze_And_Resolve (Original_Bound, Typ);
2609 return Original_Bound;
2610 end if;
2612 -- Normally, the best approach is simply to generate a constant
2613 -- declaration that captures the bound. However, there is a nasty
2614 -- case where this is wrong. If the bound is complex, and has a
2615 -- possible use of the secondary stack, we need to generate a
2616 -- separate assignment statement to ensure the creation of a block
2617 -- which will release the secondary stack.
2619 -- We prefer the constant declaration, since it leaves us with a
2620 -- proper trace of the value, useful in optimizations that get rid
2621 -- of junk range checks.
2623 if not Has_Call_Using_Secondary_Stack (Analyzed_Bound) then
2624 Analyze_And_Resolve (Original_Bound, Typ);
2626 -- Ensure that the bound is valid. This check should not be
2627 -- generated when the range belongs to a quantified expression
2628 -- as the construct is still not expanded into its final form.
2630 if Nkind (Parent (R)) /= N_Loop_Parameter_Specification
2631 or else Nkind (Parent (Parent (R))) /= N_Quantified_Expression
2632 then
2633 Ensure_Valid (Original_Bound);
2634 end if;
2636 Force_Evaluation (Original_Bound);
2637 return Original_Bound;
2638 end if;
2640 Id := Make_Temporary (Loc, 'R', Original_Bound);
2642 -- Here we make a declaration with a separate assignment
2643 -- statement, and insert before loop header.
2645 Decl :=
2646 Make_Object_Declaration (Loc,
2647 Defining_Identifier => Id,
2648 Object_Definition => New_Occurrence_Of (Typ, Loc));
2650 Assign :=
2651 Make_Assignment_Statement (Loc,
2652 Name => New_Occurrence_Of (Id, Loc),
2653 Expression => Relocate_Node (Original_Bound));
2655 Insert_Actions (Loop_Nod, New_List (Decl, Assign));
2657 -- Now that this temporary variable is initialized we decorate it
2658 -- as safe-to-reevaluate to inform to the backend that no further
2659 -- asignment will be issued and hence it can be handled as side
2660 -- effect free. Note that this decoration must be done when the
2661 -- assignment has been analyzed because otherwise it will be
2662 -- rejected (see Analyze_Assignment).
2664 Set_Is_Safe_To_Reevaluate (Id);
2666 Rewrite (Original_Bound, New_Occurrence_Of (Id, Loc));
2668 if Nkind (Assign) = N_Assignment_Statement then
2669 return Expression (Assign);
2670 else
2671 return Original_Bound;
2672 end if;
2673 end One_Bound;
2675 Hi : constant Node_Id := High_Bound (R);
2676 Lo : constant Node_Id := Low_Bound (R);
2677 R_Copy : constant Node_Id := New_Copy_Tree (R);
2678 New_Hi : Node_Id;
2679 New_Lo : Node_Id;
2680 Typ : Entity_Id;
2682 -- Start of processing for Process_Bounds
2684 begin
2685 Set_Parent (R_Copy, Parent (R));
2686 Preanalyze_Range (R_Copy);
2687 Typ := Etype (R_Copy);
2689 -- If the type of the discrete range is Universal_Integer, then the
2690 -- bound's type must be resolved to Integer, and any object used to
2691 -- hold the bound must also have type Integer, unless the literal
2692 -- bounds are constant-folded expressions with a user-defined type.
2694 if Typ = Universal_Integer then
2695 if Nkind (Lo) = N_Integer_Literal
2696 and then Present (Etype (Lo))
2697 and then Scope (Etype (Lo)) /= Standard_Standard
2698 then
2699 Typ := Etype (Lo);
2701 elsif Nkind (Hi) = N_Integer_Literal
2702 and then Present (Etype (Hi))
2703 and then Scope (Etype (Hi)) /= Standard_Standard
2704 then
2705 Typ := Etype (Hi);
2707 else
2708 Typ := Standard_Integer;
2709 end if;
2710 end if;
2712 Set_Etype (R, Typ);
2714 New_Lo := One_Bound (Lo, Low_Bound (R_Copy), Typ);
2715 New_Hi := One_Bound (Hi, High_Bound (R_Copy), Typ);
2717 -- Propagate staticness to loop range itself, in case the
2718 -- corresponding subtype is static.
2720 if New_Lo /= Lo and then Is_OK_Static_Expression (New_Lo) then
2721 Rewrite (Low_Bound (R), New_Copy (New_Lo));
2722 end if;
2724 if New_Hi /= Hi and then Is_OK_Static_Expression (New_Hi) then
2725 Rewrite (High_Bound (R), New_Copy (New_Hi));
2726 end if;
2727 end Process_Bounds;
2729 -- Local variables
2731 DS : constant Node_Id := Discrete_Subtype_Definition (N);
2732 Id : constant Entity_Id := Defining_Identifier (N);
2734 DS_Copy : Node_Id;
2736 -- Start of processing for Analyze_Loop_Parameter_Specification
2738 begin
2739 Enter_Name (Id);
2741 -- We always consider the loop variable to be referenced, since the loop
2742 -- may be used just for counting purposes.
2744 Generate_Reference (Id, N, ' ');
2746 -- Check for the case of loop variable hiding a local variable (used
2747 -- later on to give a nice warning if the hidden variable is never
2748 -- assigned).
2750 declare
2751 H : constant Entity_Id := Homonym (Id);
2752 begin
2753 if Present (H)
2754 and then Ekind (H) = E_Variable
2755 and then Is_Discrete_Type (Etype (H))
2756 and then Enclosing_Dynamic_Scope (H) = Enclosing_Dynamic_Scope (Id)
2757 then
2758 Set_Hiding_Loop_Variable (H, Id);
2759 end if;
2760 end;
2762 -- Loop parameter specification must include subtype mark in SPARK
2764 if Nkind (DS) = N_Range then
2765 Check_SPARK_05_Restriction
2766 ("loop parameter specification must include subtype mark", N);
2767 end if;
2769 -- Analyze the subtype definition and create temporaries for the bounds.
2770 -- Do not evaluate the range when preanalyzing a quantified expression
2771 -- because bounds expressed as function calls with side effects will be
2772 -- incorrectly replicated.
2774 if Nkind (DS) = N_Range
2775 and then Expander_Active
2776 and then Nkind (Parent (N)) /= N_Quantified_Expression
2777 then
2778 Process_Bounds (DS);
2780 -- Either the expander not active or the range of iteration is a subtype
2781 -- indication, an entity, or a function call that yields an aggregate or
2782 -- a container.
2784 else
2785 DS_Copy := New_Copy_Tree (DS);
2786 Set_Parent (DS_Copy, Parent (DS));
2787 Preanalyze_Range (DS_Copy);
2789 -- Ada 2012: If the domain of iteration is:
2791 -- a) a function call,
2792 -- b) an identifier that is not a type,
2793 -- c) an attribute reference 'Old (within a postcondition),
2794 -- d) an unchecked conversion or a qualified expression with
2795 -- the proper iterator type.
2797 -- then it is an iteration over a container. It was classified as
2798 -- a loop specification by the parser, and must be rewritten now
2799 -- to activate container iteration. The last case will occur within
2800 -- an expanded inlined call, where the expansion wraps an actual in
2801 -- an unchecked conversion when needed. The expression of the
2802 -- conversion is always an object.
2804 if Nkind (DS_Copy) = N_Function_Call
2806 or else (Is_Entity_Name (DS_Copy)
2807 and then not Is_Type (Entity (DS_Copy)))
2809 or else (Nkind (DS_Copy) = N_Attribute_Reference
2810 and then Nam_In (Attribute_Name (DS_Copy),
2811 Name_Loop_Entry, Name_Old))
2813 or else Has_Aspect (Etype (DS_Copy), Aspect_Iterable)
2815 or else Nkind (DS_Copy) = N_Unchecked_Type_Conversion
2816 or else (Nkind (DS_Copy) = N_Qualified_Expression
2817 and then Is_Iterator (Etype (DS_Copy)))
2818 then
2819 -- This is an iterator specification. Rewrite it as such and
2820 -- analyze it to capture function calls that may require
2821 -- finalization actions.
2823 declare
2824 I_Spec : constant Node_Id :=
2825 Make_Iterator_Specification (Sloc (N),
2826 Defining_Identifier => Relocate_Node (Id),
2827 Name => DS_Copy,
2828 Subtype_Indication => Empty,
2829 Reverse_Present => Reverse_Present (N));
2830 Scheme : constant Node_Id := Parent (N);
2832 begin
2833 Set_Iterator_Specification (Scheme, I_Spec);
2834 Set_Loop_Parameter_Specification (Scheme, Empty);
2835 Analyze_Iterator_Specification (I_Spec);
2837 -- In a generic context, analyze the original domain of
2838 -- iteration, for name capture.
2840 if not Expander_Active then
2841 Analyze (DS);
2842 end if;
2844 -- Set kind of loop parameter, which may be used in the
2845 -- subsequent analysis of the condition in a quantified
2846 -- expression.
2848 Set_Ekind (Id, E_Loop_Parameter);
2849 return;
2850 end;
2852 -- Domain of iteration is not a function call, and is side-effect
2853 -- free.
2855 else
2856 -- A quantified expression that appears in a pre/post condition
2857 -- is pre-analyzed several times. If the range is given by an
2858 -- attribute reference it is rewritten as a range, and this is
2859 -- done even with expansion disabled. If the type is already set
2860 -- do not reanalyze, because a range with static bounds may be
2861 -- typed Integer by default.
2863 if Nkind (Parent (N)) = N_Quantified_Expression
2864 and then Present (Etype (DS))
2865 then
2866 null;
2867 else
2868 Analyze (DS);
2869 end if;
2870 end if;
2871 end if;
2873 if DS = Error then
2874 return;
2875 end if;
2877 -- Some additional checks if we are iterating through a type
2879 if Is_Entity_Name (DS)
2880 and then Present (Entity (DS))
2881 and then Is_Type (Entity (DS))
2882 then
2883 -- The subtype indication may denote the completion of an incomplete
2884 -- type declaration.
2886 if Ekind (Entity (DS)) = E_Incomplete_Type then
2887 Set_Entity (DS, Get_Full_View (Entity (DS)));
2888 Set_Etype (DS, Entity (DS));
2889 end if;
2891 Check_Predicate_Use (Entity (DS));
2892 end if;
2894 -- Error if not discrete type
2896 if not Is_Discrete_Type (Etype (DS)) then
2897 Wrong_Type (DS, Any_Discrete);
2898 Set_Etype (DS, Any_Type);
2899 end if;
2901 Check_Controlled_Array_Attribute (DS);
2903 if Nkind (DS) = N_Subtype_Indication then
2904 Check_Predicate_Use (Entity (Subtype_Mark (DS)));
2905 end if;
2907 Make_Index (DS, N, In_Iter_Schm => True);
2908 Set_Ekind (Id, E_Loop_Parameter);
2910 -- A quantified expression which appears in a pre- or post-condition may
2911 -- be analyzed multiple times. The analysis of the range creates several
2912 -- itypes which reside in different scopes depending on whether the pre-
2913 -- or post-condition has been expanded. Update the type of the loop
2914 -- variable to reflect the proper itype at each stage of analysis.
2916 if No (Etype (Id))
2917 or else Etype (Id) = Any_Type
2918 or else
2919 (Present (Etype (Id))
2920 and then Is_Itype (Etype (Id))
2921 and then Nkind (Parent (Loop_Nod)) = N_Expression_With_Actions
2922 and then Nkind (Original_Node (Parent (Loop_Nod))) =
2923 N_Quantified_Expression)
2924 then
2925 Set_Etype (Id, Etype (DS));
2926 end if;
2928 -- Treat a range as an implicit reference to the type, to inhibit
2929 -- spurious warnings.
2931 Generate_Reference (Base_Type (Etype (DS)), N, ' ');
2932 Set_Is_Known_Valid (Id, True);
2934 -- The loop is not a declarative part, so the loop variable must be
2935 -- frozen explicitly. Do not freeze while preanalyzing a quantified
2936 -- expression because the freeze node will not be inserted into the
2937 -- tree due to flag Is_Spec_Expression being set.
2939 if Nkind (Parent (N)) /= N_Quantified_Expression then
2940 declare
2941 Flist : constant List_Id := Freeze_Entity (Id, N);
2942 begin
2943 if Is_Non_Empty_List (Flist) then
2944 Insert_Actions (N, Flist);
2945 end if;
2946 end;
2947 end if;
2949 -- Case where we have a range or a subtype, get type bounds
2951 if Nkind_In (DS, N_Range, N_Subtype_Indication)
2952 and then not Error_Posted (DS)
2953 and then Etype (DS) /= Any_Type
2954 and then Is_Discrete_Type (Etype (DS))
2955 then
2956 declare
2957 L : Node_Id;
2958 H : Node_Id;
2960 begin
2961 if Nkind (DS) = N_Range then
2962 L := Low_Bound (DS);
2963 H := High_Bound (DS);
2964 else
2965 L :=
2966 Type_Low_Bound (Underlying_Type (Etype (Subtype_Mark (DS))));
2967 H :=
2968 Type_High_Bound (Underlying_Type (Etype (Subtype_Mark (DS))));
2969 end if;
2971 -- Check for null or possibly null range and issue warning. We
2972 -- suppress such messages in generic templates and instances,
2973 -- because in practice they tend to be dubious in these cases. The
2974 -- check applies as well to rewritten array element loops where a
2975 -- null range may be detected statically.
2977 if Compile_Time_Compare (L, H, Assume_Valid => True) = GT then
2979 -- Suppress the warning if inside a generic template or
2980 -- instance, since in practice they tend to be dubious in these
2981 -- cases since they can result from intended parameterization.
2983 if not Inside_A_Generic and then not In_Instance then
2985 -- Specialize msg if invalid values could make the loop
2986 -- non-null after all.
2988 if Compile_Time_Compare
2989 (L, H, Assume_Valid => False) = GT
2990 then
2991 -- Since we know the range of the loop is null, set the
2992 -- appropriate flag to remove the loop entirely during
2993 -- expansion.
2995 Set_Is_Null_Loop (Loop_Nod);
2997 if Comes_From_Source (N) then
2998 Error_Msg_N
2999 ("??loop range is null, loop will not execute", DS);
3000 end if;
3002 -- Here is where the loop could execute because of
3003 -- invalid values, so issue appropriate message and in
3004 -- this case we do not set the Is_Null_Loop flag since
3005 -- the loop may execute.
3007 elsif Comes_From_Source (N) then
3008 Error_Msg_N
3009 ("??loop range may be null, loop may not execute",
3010 DS);
3011 Error_Msg_N
3012 ("??can only execute if invalid values are present",
3013 DS);
3014 end if;
3015 end if;
3017 -- In either case, suppress warnings in the body of the loop,
3018 -- since it is likely that these warnings will be inappropriate
3019 -- if the loop never actually executes, which is likely.
3021 Set_Suppress_Loop_Warnings (Loop_Nod);
3023 -- The other case for a warning is a reverse loop where the
3024 -- upper bound is the integer literal zero or one, and the
3025 -- lower bound may exceed this value.
3027 -- For example, we have
3029 -- for J in reverse N .. 1 loop
3031 -- In practice, this is very likely to be a case of reversing
3032 -- the bounds incorrectly in the range.
3034 elsif Reverse_Present (N)
3035 and then Nkind (Original_Node (H)) = N_Integer_Literal
3036 and then
3037 (Intval (Original_Node (H)) = Uint_0
3038 or else
3039 Intval (Original_Node (H)) = Uint_1)
3040 then
3041 -- Lower bound may in fact be known and known not to exceed
3042 -- upper bound (e.g. reverse 0 .. 1) and that's OK.
3044 if Compile_Time_Known_Value (L)
3045 and then Expr_Value (L) <= Expr_Value (H)
3046 then
3047 null;
3049 -- Otherwise warning is warranted
3051 else
3052 Error_Msg_N ("??loop range may be null", DS);
3053 Error_Msg_N ("\??bounds may be wrong way round", DS);
3054 end if;
3055 end if;
3057 -- Check if either bound is known to be outside the range of the
3058 -- loop parameter type, this is e.g. the case of a loop from
3059 -- 20..X where the type is 1..19.
3061 -- Such a loop is dubious since either it raises CE or it executes
3062 -- zero times, and that cannot be useful!
3064 if Etype (DS) /= Any_Type
3065 and then not Error_Posted (DS)
3066 and then Nkind (DS) = N_Subtype_Indication
3067 and then Nkind (Constraint (DS)) = N_Range_Constraint
3068 then
3069 declare
3070 LLo : constant Node_Id :=
3071 Low_Bound (Range_Expression (Constraint (DS)));
3072 LHi : constant Node_Id :=
3073 High_Bound (Range_Expression (Constraint (DS)));
3075 Bad_Bound : Node_Id := Empty;
3076 -- Suspicious loop bound
3078 begin
3079 -- At this stage L, H are the bounds of the type, and LLo
3080 -- Lhi are the low bound and high bound of the loop.
3082 if Compile_Time_Compare (LLo, L, Assume_Valid => True) = LT
3083 or else
3084 Compile_Time_Compare (LLo, H, Assume_Valid => True) = GT
3085 then
3086 Bad_Bound := LLo;
3087 end if;
3089 if Compile_Time_Compare (LHi, L, Assume_Valid => True) = LT
3090 or else
3091 Compile_Time_Compare (LHi, H, Assume_Valid => True) = GT
3092 then
3093 Bad_Bound := LHi;
3094 end if;
3096 if Present (Bad_Bound) then
3097 Error_Msg_N
3098 ("suspicious loop bound out of range of "
3099 & "loop subtype??", Bad_Bound);
3100 Error_Msg_N
3101 ("\loop executes zero times or raises "
3102 & "Constraint_Error??", Bad_Bound);
3103 end if;
3104 end;
3105 end if;
3107 -- This declare block is about warnings, if we get an exception while
3108 -- testing for warnings, we simply abandon the attempt silently. This
3109 -- most likely occurs as the result of a previous error, but might
3110 -- just be an obscure case we have missed. In either case, not giving
3111 -- the warning is perfectly acceptable.
3113 exception
3114 when others => null;
3115 end;
3116 end if;
3118 -- A loop parameter cannot be effectively volatile (SPARK RM 7.1.3(4)).
3119 -- This check is relevant only when SPARK_Mode is on as it is not a
3120 -- standard Ada legality check.
3122 if SPARK_Mode = On and then Is_Effectively_Volatile (Id) then
3123 Error_Msg_N ("loop parameter cannot be volatile", Id);
3124 end if;
3125 end Analyze_Loop_Parameter_Specification;
3127 ----------------------------
3128 -- Analyze_Loop_Statement --
3129 ----------------------------
3131 procedure Analyze_Loop_Statement (N : Node_Id) is
3133 function Is_Container_Iterator (Iter : Node_Id) return Boolean;
3134 -- Given a loop iteration scheme, determine whether it is an Ada 2012
3135 -- container iteration.
3137 function Is_Wrapped_In_Block (N : Node_Id) return Boolean;
3138 -- Determine whether loop statement N has been wrapped in a block to
3139 -- capture finalization actions that may be generated for container
3140 -- iterators. Prevents infinite recursion when block is analyzed.
3141 -- Routine is a noop if loop is single statement within source block.
3143 ---------------------------
3144 -- Is_Container_Iterator --
3145 ---------------------------
3147 function Is_Container_Iterator (Iter : Node_Id) return Boolean is
3148 begin
3149 -- Infinite loop
3151 if No (Iter) then
3152 return False;
3154 -- While loop
3156 elsif Present (Condition (Iter)) then
3157 return False;
3159 -- for Def_Id in [reverse] Name loop
3160 -- for Def_Id [: Subtype_Indication] of [reverse] Name loop
3162 elsif Present (Iterator_Specification (Iter)) then
3163 declare
3164 Nam : constant Node_Id := Name (Iterator_Specification (Iter));
3165 Nam_Copy : Node_Id;
3167 begin
3168 Nam_Copy := New_Copy_Tree (Nam);
3169 Set_Parent (Nam_Copy, Parent (Nam));
3170 Preanalyze_Range (Nam_Copy);
3172 -- The only two options here are iteration over a container or
3173 -- an array.
3175 return not Is_Array_Type (Etype (Nam_Copy));
3176 end;
3178 -- for Def_Id in [reverse] Discrete_Subtype_Definition loop
3180 else
3181 declare
3182 LP : constant Node_Id := Loop_Parameter_Specification (Iter);
3183 DS : constant Node_Id := Discrete_Subtype_Definition (LP);
3184 DS_Copy : Node_Id;
3186 begin
3187 DS_Copy := New_Copy_Tree (DS);
3188 Set_Parent (DS_Copy, Parent (DS));
3189 Preanalyze_Range (DS_Copy);
3191 -- Check for a call to Iterate () or an expression with
3192 -- an iterator type.
3194 return
3195 (Nkind (DS_Copy) = N_Function_Call
3196 and then Needs_Finalization (Etype (DS_Copy)))
3197 or else Is_Iterator (Etype (DS_Copy));
3198 end;
3199 end if;
3200 end Is_Container_Iterator;
3202 -------------------------
3203 -- Is_Wrapped_In_Block --
3204 -------------------------
3206 function Is_Wrapped_In_Block (N : Node_Id) return Boolean is
3207 HSS : Node_Id;
3208 Stat : Node_Id;
3210 begin
3212 -- Check if current scope is a block that is not a transient block.
3214 if Ekind (Current_Scope) /= E_Block
3215 or else No (Block_Node (Current_Scope))
3216 then
3217 return False;
3219 else
3220 HSS :=
3221 Handled_Statement_Sequence (Parent (Block_Node (Current_Scope)));
3223 -- Skip leading pragmas that may be introduced for invariant and
3224 -- predicate checks.
3226 Stat := First (Statements (HSS));
3227 while Present (Stat) and then Nkind (Stat) = N_Pragma loop
3228 Stat := Next (Stat);
3229 end loop;
3231 return Stat = N and then No (Next (Stat));
3232 end if;
3233 end Is_Wrapped_In_Block;
3235 -- Local declarations
3237 Id : constant Node_Id := Identifier (N);
3238 Iter : constant Node_Id := Iteration_Scheme (N);
3239 Loc : constant Source_Ptr := Sloc (N);
3240 Ent : Entity_Id;
3241 Stmt : Node_Id;
3243 -- Start of processing for Analyze_Loop_Statement
3245 begin
3246 if Present (Id) then
3248 -- Make name visible, e.g. for use in exit statements. Loop labels
3249 -- are always considered to be referenced.
3251 Analyze (Id);
3252 Ent := Entity (Id);
3254 -- Guard against serious error (typically, a scope mismatch when
3255 -- semantic analysis is requested) by creating loop entity to
3256 -- continue analysis.
3258 if No (Ent) then
3259 if Total_Errors_Detected /= 0 then
3260 Ent := New_Internal_Entity (E_Loop, Current_Scope, Loc, 'L');
3261 else
3262 raise Program_Error;
3263 end if;
3265 -- Verify that the loop name is hot hidden by an unrelated
3266 -- declaration in an inner scope.
3268 elsif Ekind (Ent) /= E_Label and then Ekind (Ent) /= E_Loop then
3269 Error_Msg_Sloc := Sloc (Ent);
3270 Error_Msg_N ("implicit label declaration for & is hidden#", Id);
3272 if Present (Homonym (Ent))
3273 and then Ekind (Homonym (Ent)) = E_Label
3274 then
3275 Set_Entity (Id, Ent);
3276 Set_Ekind (Ent, E_Loop);
3277 end if;
3279 else
3280 Generate_Reference (Ent, N, ' ');
3281 Generate_Definition (Ent);
3283 -- If we found a label, mark its type. If not, ignore it, since it
3284 -- means we have a conflicting declaration, which would already
3285 -- have been diagnosed at declaration time. Set Label_Construct
3286 -- of the implicit label declaration, which is not created by the
3287 -- parser for generic units.
3289 if Ekind (Ent) = E_Label then
3290 Set_Ekind (Ent, E_Loop);
3292 if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
3293 Set_Label_Construct (Parent (Ent), N);
3294 end if;
3295 end if;
3296 end if;
3298 -- Case of no identifier present. Create one and attach it to the
3299 -- loop statement for use as a scope and as a reference for later
3300 -- expansions. Indicate that the label does not come from source,
3301 -- and attach it to the loop statement so it is part of the tree,
3302 -- even without a full declaration.
3304 else
3305 Ent := New_Internal_Entity (E_Loop, Current_Scope, Loc, 'L');
3306 Set_Etype (Ent, Standard_Void_Type);
3307 Set_Identifier (N, New_Occurrence_Of (Ent, Loc));
3308 Set_Parent (Ent, N);
3309 Set_Has_Created_Identifier (N);
3310 end if;
3312 -- If the iterator specification has a syntactic error, transform
3313 -- construct into an infinite loop to prevent a crash and perform
3314 -- some analysis.
3316 if Present (Iter)
3317 and then Present (Iterator_Specification (Iter))
3318 and then Error_Posted (Iterator_Specification (Iter))
3319 then
3320 Set_Iteration_Scheme (N, Empty);
3321 Analyze (N);
3322 return;
3323 end if;
3325 -- Iteration over a container in Ada 2012 involves the creation of a
3326 -- controlled iterator object. Wrap the loop in a block to ensure the
3327 -- timely finalization of the iterator and release of container locks.
3328 -- The same applies to the use of secondary stack when obtaining an
3329 -- iterator.
3331 if Ada_Version >= Ada_2012
3332 and then Is_Container_Iterator (Iter)
3333 and then not Is_Wrapped_In_Block (N)
3334 then
3335 declare
3336 Block_Nod : Node_Id;
3337 Block_Id : Entity_Id;
3339 begin
3340 Block_Nod :=
3341 Make_Block_Statement (Loc,
3342 Declarations => New_List,
3343 Handled_Statement_Sequence =>
3344 Make_Handled_Sequence_Of_Statements (Loc,
3345 Statements => New_List (Relocate_Node (N))));
3347 Add_Block_Identifier (Block_Nod, Block_Id);
3349 -- The expansion of iterator loops generates an iterator in order
3350 -- to traverse the elements of a container:
3352 -- Iter : <iterator type> := Iterate (Container)'reference;
3354 -- The iterator is controlled and returned on the secondary stack.
3355 -- The analysis of the call to Iterate establishes a transient
3356 -- scope to deal with the secondary stack management, but never
3357 -- really creates a physical block as this would kill the iterator
3358 -- too early (see Wrap_Transient_Declaration). To address this
3359 -- case, mark the generated block as needing secondary stack
3360 -- management.
3362 Set_Uses_Sec_Stack (Block_Id);
3364 Rewrite (N, Block_Nod);
3365 Analyze (N);
3366 return;
3367 end;
3368 end if;
3370 -- Kill current values on entry to loop, since statements in the body of
3371 -- the loop may have been executed before the loop is entered. Similarly
3372 -- we kill values after the loop, since we do not know that the body of
3373 -- the loop was executed.
3375 Kill_Current_Values;
3376 Push_Scope (Ent);
3377 Analyze_Iteration_Scheme (Iter);
3379 -- Check for following case which merits a warning if the type E of is
3380 -- a multi-dimensional array (and no explicit subscript ranges present).
3382 -- for J in E'Range
3383 -- for K in E'Range
3385 if Present (Iter)
3386 and then Present (Loop_Parameter_Specification (Iter))
3387 then
3388 declare
3389 LPS : constant Node_Id := Loop_Parameter_Specification (Iter);
3390 DSD : constant Node_Id :=
3391 Original_Node (Discrete_Subtype_Definition (LPS));
3392 begin
3393 if Nkind (DSD) = N_Attribute_Reference
3394 and then Attribute_Name (DSD) = Name_Range
3395 and then No (Expressions (DSD))
3396 then
3397 declare
3398 Typ : constant Entity_Id := Etype (Prefix (DSD));
3399 begin
3400 if Is_Array_Type (Typ)
3401 and then Number_Dimensions (Typ) > 1
3402 and then Nkind (Parent (N)) = N_Loop_Statement
3403 and then Present (Iteration_Scheme (Parent (N)))
3404 then
3405 declare
3406 OIter : constant Node_Id :=
3407 Iteration_Scheme (Parent (N));
3408 OLPS : constant Node_Id :=
3409 Loop_Parameter_Specification (OIter);
3410 ODSD : constant Node_Id :=
3411 Original_Node (Discrete_Subtype_Definition (OLPS));
3412 begin
3413 if Nkind (ODSD) = N_Attribute_Reference
3414 and then Attribute_Name (ODSD) = Name_Range
3415 and then No (Expressions (ODSD))
3416 and then Etype (Prefix (ODSD)) = Typ
3417 then
3418 Error_Msg_Sloc := Sloc (ODSD);
3419 Error_Msg_N
3420 ("inner range same as outer range#??", DSD);
3421 end if;
3422 end;
3423 end if;
3424 end;
3425 end if;
3426 end;
3427 end if;
3429 -- Analyze the statements of the body except in the case of an Ada 2012
3430 -- iterator with the expander active. In this case the expander will do
3431 -- a rewrite of the loop into a while loop. We will then analyze the
3432 -- loop body when we analyze this while loop.
3434 -- We need to do this delay because if the container is for indefinite
3435 -- types the actual subtype of the components will only be determined
3436 -- when the cursor declaration is analyzed.
3438 -- If the expander is not active then we want to analyze the loop body
3439 -- now even in the Ada 2012 iterator case, since the rewriting will not
3440 -- be done. Insert the loop variable in the current scope, if not done
3441 -- when analysing the iteration scheme. Set its kind properly to detect
3442 -- improper uses in the loop body.
3444 -- In GNATprove mode, we do one of the above depending on the kind of
3445 -- loop. If it is an iterator over an array, then we do not analyze the
3446 -- loop now. We will analyze it after it has been rewritten by the
3447 -- special SPARK expansion which is activated in GNATprove mode. We need
3448 -- to do this so that other expansions that should occur in GNATprove
3449 -- mode take into account the specificities of the rewritten loop, in
3450 -- particular the introduction of a renaming (which needs to be
3451 -- expanded).
3453 -- In other cases in GNATprove mode then we want to analyze the loop
3454 -- body now, since no rewriting will occur. Within a generic the
3455 -- GNATprove mode is irrelevant, we must analyze the generic for
3456 -- non-local name capture.
3458 if Present (Iter)
3459 and then Present (Iterator_Specification (Iter))
3460 then
3461 if GNATprove_Mode
3462 and then Is_Iterator_Over_Array (Iterator_Specification (Iter))
3463 and then not Inside_A_Generic
3464 then
3465 null;
3467 elsif not Expander_Active then
3468 declare
3469 I_Spec : constant Node_Id := Iterator_Specification (Iter);
3470 Id : constant Entity_Id := Defining_Identifier (I_Spec);
3472 begin
3473 if Scope (Id) /= Current_Scope then
3474 Enter_Name (Id);
3475 end if;
3477 -- In an element iterator, The loop parameter is a variable if
3478 -- the domain of iteration (container or array) is a variable.
3480 if not Of_Present (I_Spec)
3481 or else not Is_Variable (Name (I_Spec))
3482 then
3483 Set_Ekind (Id, E_Loop_Parameter);
3484 end if;
3485 end;
3487 Analyze_Statements (Statements (N));
3488 end if;
3490 else
3492 -- Pre-Ada2012 for-loops and while loops.
3494 Analyze_Statements (Statements (N));
3495 end if;
3497 -- When the iteration scheme of a loop contains attribute 'Loop_Entry,
3498 -- the loop is transformed into a conditional block. Retrieve the loop.
3500 Stmt := N;
3502 if Subject_To_Loop_Entry_Attributes (Stmt) then
3503 Stmt := Find_Loop_In_Conditional_Block (Stmt);
3504 end if;
3506 -- Finish up processing for the loop. We kill all current values, since
3507 -- in general we don't know if the statements in the loop have been
3508 -- executed. We could do a bit better than this with a loop that we
3509 -- know will execute at least once, but it's not worth the trouble and
3510 -- the front end is not in the business of flow tracing.
3512 Process_End_Label (Stmt, 'e', Ent);
3513 End_Scope;
3514 Kill_Current_Values;
3516 -- Check for infinite loop. Skip check for generated code, since it
3517 -- justs waste time and makes debugging the routine called harder.
3519 -- Note that we have to wait till the body of the loop is fully analyzed
3520 -- before making this call, since Check_Infinite_Loop_Warning relies on
3521 -- being able to use semantic visibility information to find references.
3523 if Comes_From_Source (Stmt) then
3524 Check_Infinite_Loop_Warning (Stmt);
3525 end if;
3527 -- Code after loop is unreachable if the loop has no WHILE or FOR and
3528 -- contains no EXIT statements within the body of the loop.
3530 if No (Iter) and then not Has_Exit (Ent) then
3531 Check_Unreachable_Code (Stmt);
3532 end if;
3533 end Analyze_Loop_Statement;
3535 ----------------------------
3536 -- Analyze_Null_Statement --
3537 ----------------------------
3539 -- Note: the semantics of the null statement is implemented by a single
3540 -- null statement, too bad everything isn't as simple as this.
3542 procedure Analyze_Null_Statement (N : Node_Id) is
3543 pragma Warnings (Off, N);
3544 begin
3545 null;
3546 end Analyze_Null_Statement;
3548 -------------------------
3549 -- Analyze_Target_Name --
3550 -------------------------
3552 procedure Analyze_Target_Name (N : Node_Id) is
3553 begin
3554 -- A target name has the type of the left-hand side of the enclosing
3555 -- assignment.
3557 Set_Etype (N, Etype (Name (Current_Assignment)));
3558 end Analyze_Target_Name;
3560 ------------------------
3561 -- Analyze_Statements --
3562 ------------------------
3564 procedure Analyze_Statements (L : List_Id) is
3565 Lab : Entity_Id;
3566 S : Node_Id;
3568 begin
3569 -- The labels declared in the statement list are reachable from
3570 -- statements in the list. We do this as a prepass so that any goto
3571 -- statement will be properly flagged if its target is not reachable.
3572 -- This is not required, but is nice behavior.
3574 S := First (L);
3575 while Present (S) loop
3576 if Nkind (S) = N_Label then
3577 Analyze (Identifier (S));
3578 Lab := Entity (Identifier (S));
3580 -- If we found a label mark it as reachable
3582 if Ekind (Lab) = E_Label then
3583 Generate_Definition (Lab);
3584 Set_Reachable (Lab);
3586 if Nkind (Parent (Lab)) = N_Implicit_Label_Declaration then
3587 Set_Label_Construct (Parent (Lab), S);
3588 end if;
3590 -- If we failed to find a label, it means the implicit declaration
3591 -- of the label was hidden. A for-loop parameter can do this to
3592 -- a label with the same name inside the loop, since the implicit
3593 -- label declaration is in the innermost enclosing body or block
3594 -- statement.
3596 else
3597 Error_Msg_Sloc := Sloc (Lab);
3598 Error_Msg_N
3599 ("implicit label declaration for & is hidden#",
3600 Identifier (S));
3601 end if;
3602 end if;
3604 Next (S);
3605 end loop;
3607 -- Perform semantic analysis on all statements
3609 Conditional_Statements_Begin;
3611 S := First (L);
3612 while Present (S) loop
3613 Analyze (S);
3615 -- Remove dimension in all statements
3617 Remove_Dimension_In_Statement (S);
3618 Next (S);
3619 end loop;
3621 Conditional_Statements_End;
3623 -- Make labels unreachable. Visibility is not sufficient, because labels
3624 -- in one if-branch for example are not reachable from the other branch,
3625 -- even though their declarations are in the enclosing declarative part.
3627 S := First (L);
3628 while Present (S) loop
3629 if Nkind (S) = N_Label then
3630 Set_Reachable (Entity (Identifier (S)), False);
3631 end if;
3633 Next (S);
3634 end loop;
3635 end Analyze_Statements;
3637 ----------------------------
3638 -- Check_Unreachable_Code --
3639 ----------------------------
3641 procedure Check_Unreachable_Code (N : Node_Id) is
3642 Error_Node : Node_Id;
3643 P : Node_Id;
3645 begin
3646 if Is_List_Member (N) and then Comes_From_Source (N) then
3647 declare
3648 Nxt : Node_Id;
3650 begin
3651 Nxt := Original_Node (Next (N));
3653 -- Skip past pragmas
3655 while Nkind (Nxt) = N_Pragma loop
3656 Nxt := Original_Node (Next (Nxt));
3657 end loop;
3659 -- If a label follows us, then we never have dead code, since
3660 -- someone could branch to the label, so we just ignore it, unless
3661 -- we are in formal mode where goto statements are not allowed.
3663 if Nkind (Nxt) = N_Label
3664 and then not Restriction_Check_Required (SPARK_05)
3665 then
3666 return;
3668 -- Otherwise see if we have a real statement following us
3670 elsif Present (Nxt)
3671 and then Comes_From_Source (Nxt)
3672 and then Is_Statement (Nxt)
3673 then
3674 -- Special very annoying exception. If we have a return that
3675 -- follows a raise, then we allow it without a warning, since
3676 -- the Ada RM annoyingly requires a useless return here.
3678 if Nkind (Original_Node (N)) /= N_Raise_Statement
3679 or else Nkind (Nxt) /= N_Simple_Return_Statement
3680 then
3681 -- The rather strange shenanigans with the warning message
3682 -- here reflects the fact that Kill_Dead_Code is very good
3683 -- at removing warnings in deleted code, and this is one
3684 -- warning we would prefer NOT to have removed.
3686 Error_Node := Nxt;
3688 -- If we have unreachable code, analyze and remove the
3689 -- unreachable code, since it is useless and we don't
3690 -- want to generate junk warnings.
3692 -- We skip this step if we are not in code generation mode
3693 -- or CodePeer mode.
3695 -- This is the one case where we remove dead code in the
3696 -- semantics as opposed to the expander, and we do not want
3697 -- to remove code if we are not in code generation mode,
3698 -- since this messes up the ASIS trees or loses useful
3699 -- information in the CodePeer tree.
3701 -- Note that one might react by moving the whole circuit to
3702 -- exp_ch5, but then we lose the warning in -gnatc mode.
3704 if Operating_Mode = Generate_Code
3705 and then not CodePeer_Mode
3706 then
3707 loop
3708 Nxt := Next (N);
3710 -- Quit deleting when we have nothing more to delete
3711 -- or if we hit a label (since someone could transfer
3712 -- control to a label, so we should not delete it).
3714 exit when No (Nxt) or else Nkind (Nxt) = N_Label;
3716 -- Statement/declaration is to be deleted
3718 Analyze (Nxt);
3719 Remove (Nxt);
3720 Kill_Dead_Code (Nxt);
3721 end loop;
3722 end if;
3724 -- Now issue the warning (or error in formal mode)
3726 if Restriction_Check_Required (SPARK_05) then
3727 Check_SPARK_05_Restriction
3728 ("unreachable code is not allowed", Error_Node);
3729 else
3730 Error_Msg ("??unreachable code!", Sloc (Error_Node));
3731 end if;
3732 end if;
3734 -- If the unconditional transfer of control instruction is the
3735 -- last statement of a sequence, then see if our parent is one of
3736 -- the constructs for which we count unblocked exits, and if so,
3737 -- adjust the count.
3739 else
3740 P := Parent (N);
3742 -- Statements in THEN part or ELSE part of IF statement
3744 if Nkind (P) = N_If_Statement then
3745 null;
3747 -- Statements in ELSIF part of an IF statement
3749 elsif Nkind (P) = N_Elsif_Part then
3750 P := Parent (P);
3751 pragma Assert (Nkind (P) = N_If_Statement);
3753 -- Statements in CASE statement alternative
3755 elsif Nkind (P) = N_Case_Statement_Alternative then
3756 P := Parent (P);
3757 pragma Assert (Nkind (P) = N_Case_Statement);
3759 -- Statements in body of block
3761 elsif Nkind (P) = N_Handled_Sequence_Of_Statements
3762 and then Nkind (Parent (P)) = N_Block_Statement
3763 then
3764 -- The original loop is now placed inside a block statement
3765 -- due to the expansion of attribute 'Loop_Entry. Return as
3766 -- this is not a "real" block for the purposes of exit
3767 -- counting.
3769 if Nkind (N) = N_Loop_Statement
3770 and then Subject_To_Loop_Entry_Attributes (N)
3771 then
3772 return;
3773 end if;
3775 -- Statements in exception handler in a block
3777 elsif Nkind (P) = N_Exception_Handler
3778 and then Nkind (Parent (P)) = N_Handled_Sequence_Of_Statements
3779 and then Nkind (Parent (Parent (P))) = N_Block_Statement
3780 then
3781 null;
3783 -- None of these cases, so return
3785 else
3786 return;
3787 end if;
3789 -- This was one of the cases we are looking for (i.e. the
3790 -- parent construct was IF, CASE or block) so decrement count.
3792 Unblocked_Exit_Count := Unblocked_Exit_Count - 1;
3793 end if;
3794 end;
3795 end if;
3796 end Check_Unreachable_Code;
3798 ----------------------
3799 -- Preanalyze_Range --
3800 ----------------------
3802 procedure Preanalyze_Range (R_Copy : Node_Id) is
3803 Save_Analysis : constant Boolean := Full_Analysis;
3804 Typ : Entity_Id;
3806 begin
3807 Full_Analysis := False;
3808 Expander_Mode_Save_And_Set (False);
3810 Analyze (R_Copy);
3812 if Nkind (R_Copy) in N_Subexpr and then Is_Overloaded (R_Copy) then
3814 -- Apply preference rules for range of predefined integer types, or
3815 -- check for array or iterable construct for "of" iterator, or
3816 -- diagnose true ambiguity.
3818 declare
3819 I : Interp_Index;
3820 It : Interp;
3821 Found : Entity_Id := Empty;
3823 begin
3824 Get_First_Interp (R_Copy, I, It);
3825 while Present (It.Typ) loop
3826 if Is_Discrete_Type (It.Typ) then
3827 if No (Found) then
3828 Found := It.Typ;
3829 else
3830 if Scope (Found) = Standard_Standard then
3831 null;
3833 elsif Scope (It.Typ) = Standard_Standard then
3834 Found := It.Typ;
3836 else
3837 -- Both of them are user-defined
3839 Error_Msg_N
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);
3844 exit;
3845 end if;
3846 end if;
3848 elsif Nkind (Parent (R_Copy)) = N_Iterator_Specification
3849 and then Of_Present (Parent (R_Copy))
3850 then
3851 if Is_Array_Type (It.Typ)
3852 or else Has_Aspect (It.Typ, Aspect_Iterator_Element)
3853 or else Has_Aspect (It.Typ, Aspect_Constant_Indexing)
3854 or else Has_Aspect (It.Typ, Aspect_Variable_Indexing)
3855 then
3856 if No (Found) then
3857 Found := It.Typ;
3858 Set_Etype (R_Copy, It.Typ);
3860 else
3861 Error_Msg_N ("ambiguous domain of iteration", R_Copy);
3862 end if;
3863 end if;
3864 end if;
3866 Get_Next_Interp (I, It);
3867 end loop;
3868 end;
3869 end if;
3871 -- Subtype mark in iteration scheme
3873 if Is_Entity_Name (R_Copy) and then Is_Type (Entity (R_Copy)) then
3874 null;
3876 -- Expression in range, or Ada 2012 iterator
3878 elsif Nkind (R_Copy) in N_Subexpr then
3879 Resolve (R_Copy);
3880 Typ := Etype (R_Copy);
3882 if Is_Discrete_Type (Typ) then
3883 null;
3885 -- Check that the resulting object is an iterable container
3887 elsif Has_Aspect (Typ, Aspect_Iterator_Element)
3888 or else Has_Aspect (Typ, Aspect_Constant_Indexing)
3889 or else Has_Aspect (Typ, Aspect_Variable_Indexing)
3890 then
3891 null;
3893 -- The expression may yield an implicit reference to an iterable
3894 -- container. Insert explicit dereference so that proper type is
3895 -- visible in the loop.
3897 elsif Has_Implicit_Dereference (Etype (R_Copy)) then
3898 declare
3899 Disc : Entity_Id;
3901 begin
3902 Disc := First_Discriminant (Typ);
3903 while Present (Disc) loop
3904 if Has_Implicit_Dereference (Disc) then
3905 Build_Explicit_Dereference (R_Copy, Disc);
3906 exit;
3907 end if;
3909 Next_Discriminant (Disc);
3910 end loop;
3911 end;
3913 end if;
3914 end if;
3916 Expander_Mode_Restore;
3917 Full_Analysis := Save_Analysis;
3918 end Preanalyze_Range;
3920 end Sem_Ch5;