Fix date
[official-gcc.git] / gcc / ada / sem_ch5.adb
blobe72dc4bf7c2295b5fa817e30c2704b534a72283a
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 -- If the target of the assignment is an entity of a mutable type and
584 -- the expression is a conditional expression, its alternatives can be
585 -- of different subtypes of the nominal type of the LHS, so they must be
586 -- resolved with the base type, given that their subtype may differ from
587 -- that of the target mutable object.
589 if Is_Entity_Name (Lhs)
590 and then Ekind_In (Entity (Lhs), E_In_Out_Parameter,
591 E_Out_Parameter,
592 E_Variable)
593 and then Is_Composite_Type (T1)
594 and then not Is_Constrained (Etype (Entity (Lhs)))
595 and then Nkind_In (Rhs, N_If_Expression, N_Case_Expression)
596 then
597 Resolve (Rhs, Base_Type (T1));
599 else
600 Resolve (Rhs, T1);
601 end if;
603 -- This is the point at which we check for an unset reference
605 Check_Unset_Reference (Rhs);
606 Check_Unprotected_Access (Lhs, Rhs);
608 -- Remaining steps are skipped if Rhs was syntactically in error
610 if Rhs = Error then
611 Kill_Lhs;
612 goto Leave;
613 end if;
615 T2 := Etype (Rhs);
617 if not Covers (T1, T2) then
618 Wrong_Type (Rhs, Etype (Lhs));
619 Kill_Lhs;
620 goto Leave;
621 end if;
623 -- Ada 2005 (AI-326): In case of explicit dereference of incomplete
624 -- types, use the non-limited view if available
626 if Nkind (Rhs) = N_Explicit_Dereference
627 and then Is_Tagged_Type (T2)
628 and then Has_Non_Limited_View (T2)
629 then
630 T2 := Non_Limited_View (T2);
631 end if;
633 Set_Assignment_Type (Rhs, T2);
635 if Total_Errors_Detected /= 0 then
636 if No (T1) then
637 T1 := Any_Type;
638 end if;
640 if No (T2) then
641 T2 := Any_Type;
642 end if;
643 end if;
645 if T1 = Any_Type or else T2 = Any_Type then
646 Kill_Lhs;
647 goto Leave;
648 end if;
650 -- If the rhs is class-wide or dynamically tagged, then require the lhs
651 -- to be class-wide. The case where the rhs is a dynamically tagged call
652 -- to a dispatching operation with a controlling access result is
653 -- excluded from this check, since the target has an access type (and
654 -- no tag propagation occurs in that case).
656 if (Is_Class_Wide_Type (T2)
657 or else (Is_Dynamically_Tagged (Rhs)
658 and then not Is_Access_Type (T1)))
659 and then not Is_Class_Wide_Type (T1)
660 then
661 Error_Msg_N ("dynamically tagged expression not allowed!", Rhs);
663 elsif Is_Class_Wide_Type (T1)
664 and then not Is_Class_Wide_Type (T2)
665 and then not Is_Tag_Indeterminate (Rhs)
666 and then not Is_Dynamically_Tagged (Rhs)
667 then
668 Error_Msg_N ("dynamically tagged expression required!", Rhs);
669 end if;
671 -- Propagate the tag from a class-wide target to the rhs when the rhs
672 -- is a tag-indeterminate call.
674 if Is_Tag_Indeterminate (Rhs) then
675 if Is_Class_Wide_Type (T1) then
676 Propagate_Tag (Lhs, Rhs);
678 elsif Nkind (Rhs) = N_Function_Call
679 and then Is_Entity_Name (Name (Rhs))
680 and then Is_Abstract_Subprogram (Entity (Name (Rhs)))
681 then
682 Error_Msg_N
683 ("call to abstract function must be dispatching", Name (Rhs));
685 elsif Nkind (Rhs) = N_Qualified_Expression
686 and then Nkind (Expression (Rhs)) = N_Function_Call
687 and then Is_Entity_Name (Name (Expression (Rhs)))
688 and then
689 Is_Abstract_Subprogram (Entity (Name (Expression (Rhs))))
690 then
691 Error_Msg_N
692 ("call to abstract function must be dispatching",
693 Name (Expression (Rhs)));
694 end if;
695 end if;
697 -- Ada 2005 (AI-385): When the lhs type is an anonymous access type,
698 -- apply an implicit conversion of the rhs to that type to force
699 -- appropriate static and run-time accessibility checks. This applies
700 -- as well to anonymous access-to-subprogram types that are component
701 -- subtypes or formal parameters.
703 if Ada_Version >= Ada_2005 and then Is_Access_Type (T1) then
704 if Is_Local_Anonymous_Access (T1)
705 or else Ekind (T2) = E_Anonymous_Access_Subprogram_Type
707 -- Handle assignment to an Ada 2012 stand-alone object
708 -- of an anonymous access type.
710 or else (Ekind (T1) = E_Anonymous_Access_Type
711 and then Nkind (Associated_Node_For_Itype (T1)) =
712 N_Object_Declaration)
714 then
715 Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
716 Analyze_And_Resolve (Rhs, T1);
717 end if;
718 end if;
720 -- Ada 2005 (AI-231): Assignment to not null variable
722 if Ada_Version >= Ada_2005
723 and then Can_Never_Be_Null (T1)
724 and then not Assignment_OK (Lhs)
725 then
726 -- Case where we know the right hand side is null
728 if Known_Null (Rhs) then
729 Apply_Compile_Time_Constraint_Error
730 (N => Rhs,
731 Msg =>
732 "(Ada 2005) null not allowed in null-excluding objects??",
733 Reason => CE_Null_Not_Allowed);
735 -- We still mark this as a possible modification, that's necessary
736 -- to reset Is_True_Constant, and desirable for xref purposes.
738 Note_Possible_Modification (Lhs, Sure => True);
739 goto Leave;
741 -- If we know the right hand side is non-null, then we convert to the
742 -- target type, since we don't need a run time check in that case.
744 elsif not Can_Never_Be_Null (T2) then
745 Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
746 Analyze_And_Resolve (Rhs, T1);
747 end if;
748 end if;
750 if Is_Scalar_Type (T1) then
751 Apply_Scalar_Range_Check (Rhs, Etype (Lhs));
753 -- For array types, verify that lengths match. If the right hand side
754 -- is a function call that has been inlined, the assignment has been
755 -- rewritten as a block, and the constraint check will be applied to the
756 -- assignment within the block.
758 elsif Is_Array_Type (T1)
759 and then (Nkind (Rhs) /= N_Type_Conversion
760 or else Is_Constrained (Etype (Rhs)))
761 and then (Nkind (Rhs) /= N_Function_Call
762 or else Nkind (N) /= N_Block_Statement)
763 then
764 -- Assignment verifies that the length of the Lsh and Rhs are equal,
765 -- but of course the indexes do not have to match. If the right-hand
766 -- side is a type conversion to an unconstrained type, a length check
767 -- is performed on the expression itself during expansion. In rare
768 -- cases, the redundant length check is computed on an index type
769 -- with a different representation, triggering incorrect code in the
770 -- back end.
772 Apply_Length_Check (Rhs, Etype (Lhs));
774 else
775 -- Discriminant checks are applied in the course of expansion
777 null;
778 end if;
780 -- Note: modifications of the Lhs may only be recorded after
781 -- checks have been applied.
783 Note_Possible_Modification (Lhs, Sure => True);
785 -- ??? a real accessibility check is needed when ???
787 -- Post warning for redundant assignment or variable to itself
789 if Warn_On_Redundant_Constructs
791 -- We only warn for source constructs
793 and then Comes_From_Source (N)
795 -- Where the object is the same on both sides
797 and then Same_Object (Lhs, Original_Node (Rhs))
799 -- But exclude the case where the right side was an operation that
800 -- got rewritten (e.g. JUNK + K, where K was known to be zero). We
801 -- don't want to warn in such a case, since it is reasonable to write
802 -- such expressions especially when K is defined symbolically in some
803 -- other package.
805 and then Nkind (Original_Node (Rhs)) not in N_Op
806 then
807 if Nkind (Lhs) in N_Has_Entity then
808 Error_Msg_NE -- CODEFIX
809 ("?r?useless assignment of & to itself!", N, Entity (Lhs));
810 else
811 Error_Msg_N -- CODEFIX
812 ("?r?useless assignment of object to itself!", N);
813 end if;
814 end if;
816 -- Check for non-allowed composite assignment
818 if not Support_Composite_Assign_On_Target
819 and then (Is_Array_Type (T1) or else Is_Record_Type (T1))
820 and then (not Has_Size_Clause (T1) or else Esize (T1) > 64)
821 then
822 Error_Msg_CRT ("composite assignment", N);
823 end if;
825 -- Check elaboration warning for left side if not in elab code
827 if not In_Subprogram_Or_Concurrent_Unit then
828 Check_Elab_Assign (Lhs);
829 end if;
831 -- Set Referenced_As_LHS if appropriate. We only set this flag if the
832 -- assignment is a source assignment in the extended main source unit.
833 -- We are not interested in any reference information outside this
834 -- context, or in compiler generated assignment statements.
836 if Comes_From_Source (N)
837 and then In_Extended_Main_Source_Unit (Lhs)
838 then
839 Set_Referenced_Modified (Lhs, Out_Param => False);
840 end if;
842 -- RM 7.3.2 (12/3): An assignment to a view conversion (from a type
843 -- to one of its ancestors) requires an invariant check. Apply check
844 -- only if expression comes from source, otherwise it will be applied
845 -- when value is assigned to source entity.
847 if Nkind (Lhs) = N_Type_Conversion
848 and then Has_Invariants (Etype (Expression (Lhs)))
849 and then Comes_From_Source (Expression (Lhs))
850 then
851 Insert_After (N, Make_Invariant_Call (Expression (Lhs)));
852 end if;
854 -- Final step. If left side is an entity, then we may be able to reset
855 -- the current tracked values to new safe values. We only have something
856 -- to do if the left side is an entity name, and expansion has not
857 -- modified the node into something other than an assignment, and of
858 -- course we only capture values if it is safe to do so.
860 if Is_Entity_Name (Lhs)
861 and then Nkind (N) = N_Assignment_Statement
862 then
863 declare
864 Ent : constant Entity_Id := Entity (Lhs);
866 begin
867 if Safe_To_Capture_Value (N, Ent) then
869 -- If simple variable on left side, warn if this assignment
870 -- blots out another one (rendering it useless). We only do
871 -- this for source assignments, otherwise we can generate bogus
872 -- warnings when an assignment is rewritten as another
873 -- assignment, and gets tied up with itself.
875 -- There may have been a previous reference to a component of
876 -- the variable, which in general removes the Last_Assignment
877 -- field of the variable to indicate a relevant use of the
878 -- previous assignment. However, if the assignment is to a
879 -- subcomponent the reference may not have registered, because
880 -- it is not possible to determine whether the context is an
881 -- assignment. In those cases we generate a Deferred_Reference,
882 -- to be used at the end of compilation to generate the right
883 -- kind of reference, and we suppress a potential warning for
884 -- a useless assignment, which might be premature. This may
885 -- lose a warning in rare cases, but seems preferable to a
886 -- misleading warning.
888 if Warn_On_Modified_Unread
889 and then Is_Assignable (Ent)
890 and then Comes_From_Source (N)
891 and then In_Extended_Main_Source_Unit (Ent)
892 and then not Has_Deferred_Reference (Ent)
893 then
894 Warn_On_Useless_Assignment (Ent, N);
895 end if;
897 -- If we are assigning an access type and the left side is an
898 -- entity, then make sure that the Is_Known_[Non_]Null flags
899 -- properly reflect the state of the entity after assignment.
901 if Is_Access_Type (T1) then
902 if Known_Non_Null (Rhs) then
903 Set_Is_Known_Non_Null (Ent, True);
905 elsif Known_Null (Rhs)
906 and then not Can_Never_Be_Null (Ent)
907 then
908 Set_Is_Known_Null (Ent, True);
910 else
911 Set_Is_Known_Null (Ent, False);
913 if not Can_Never_Be_Null (Ent) then
914 Set_Is_Known_Non_Null (Ent, False);
915 end if;
916 end if;
918 -- For discrete types, we may be able to set the current value
919 -- if the value is known at compile time.
921 elsif Is_Discrete_Type (T1)
922 and then Compile_Time_Known_Value (Rhs)
923 then
924 Set_Current_Value (Ent, Rhs);
925 else
926 Set_Current_Value (Ent, Empty);
927 end if;
929 -- If not safe to capture values, kill them
931 else
932 Kill_Lhs;
933 end if;
934 end;
935 end if;
937 -- If assigning to an object in whole or in part, note location of
938 -- assignment in case no one references value. We only do this for
939 -- source assignments, otherwise we can generate bogus warnings when an
940 -- assignment is rewritten as another assignment, and gets tied up with
941 -- itself.
943 declare
944 Ent : constant Entity_Id := Get_Enclosing_Object (Lhs);
945 begin
946 if Present (Ent)
947 and then Safe_To_Capture_Value (N, Ent)
948 and then Nkind (N) = N_Assignment_Statement
949 and then Warn_On_Modified_Unread
950 and then Is_Assignable (Ent)
951 and then Comes_From_Source (N)
952 and then In_Extended_Main_Source_Unit (Ent)
953 then
954 Set_Last_Assignment (Ent, Lhs);
955 end if;
956 end;
958 Analyze_Dimension (N);
960 <<Leave>>
961 Restore_Ghost_Mode (Saved_GM);
963 -- If the right-hand side contains target names, expansion has been
964 -- disabled to prevent expansion that might move target names out of
965 -- the context of the assignment statement. Restore the expander mode
966 -- now so that assignment statement can be properly expanded.
968 if Nkind (N) = N_Assignment_Statement and then Has_Target_Names (N) then
969 Expander_Mode_Restore;
970 Full_Analysis := Save_Full_Analysis;
971 end if;
972 end Analyze_Assignment;
974 -----------------------------
975 -- Analyze_Block_Statement --
976 -----------------------------
978 procedure Analyze_Block_Statement (N : Node_Id) is
979 procedure Install_Return_Entities (Scop : Entity_Id);
980 -- Install all entities of return statement scope Scop in the visibility
981 -- chain except for the return object since its entity is reused in a
982 -- renaming.
984 -----------------------------
985 -- Install_Return_Entities --
986 -----------------------------
988 procedure Install_Return_Entities (Scop : Entity_Id) is
989 Id : Entity_Id;
991 begin
992 Id := First_Entity (Scop);
993 while Present (Id) loop
995 -- Do not install the return object
997 if not Ekind_In (Id, E_Constant, E_Variable)
998 or else not Is_Return_Object (Id)
999 then
1000 Install_Entity (Id);
1001 end if;
1003 Next_Entity (Id);
1004 end loop;
1005 end Install_Return_Entities;
1007 -- Local constants and variables
1009 Decls : constant List_Id := Declarations (N);
1010 Id : constant Node_Id := Identifier (N);
1011 HSS : constant Node_Id := Handled_Statement_Sequence (N);
1013 Is_BIP_Return_Statement : Boolean;
1015 -- Start of processing for Analyze_Block_Statement
1017 begin
1018 -- In SPARK mode, we reject block statements. Note that the case of
1019 -- block statements generated by the expander is fine.
1021 if Nkind (Original_Node (N)) = N_Block_Statement then
1022 Check_SPARK_05_Restriction ("block statement is not allowed", N);
1023 end if;
1025 -- If no handled statement sequence is present, things are really messed
1026 -- up, and we just return immediately (defence against previous errors).
1028 if No (HSS) then
1029 Check_Error_Detected;
1030 return;
1031 end if;
1033 -- Detect whether the block is actually a rewritten return statement of
1034 -- a build-in-place function.
1036 Is_BIP_Return_Statement :=
1037 Present (Id)
1038 and then Present (Entity (Id))
1039 and then Ekind (Entity (Id)) = E_Return_Statement
1040 and then Is_Build_In_Place_Function
1041 (Return_Applies_To (Entity (Id)));
1043 -- Normal processing with HSS present
1045 declare
1046 EH : constant List_Id := Exception_Handlers (HSS);
1047 Ent : Entity_Id := Empty;
1048 S : Entity_Id;
1050 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1051 -- Recursively save value of this global, will be restored on exit
1053 begin
1054 -- Initialize unblocked exit count for statements of begin block
1055 -- plus one for each exception handler that is present.
1057 Unblocked_Exit_Count := 1;
1059 if Present (EH) then
1060 Unblocked_Exit_Count := Unblocked_Exit_Count + List_Length (EH);
1061 end if;
1063 -- If a label is present analyze it and mark it as referenced
1065 if Present (Id) then
1066 Analyze (Id);
1067 Ent := Entity (Id);
1069 -- An error defense. If we have an identifier, but no entity, then
1070 -- something is wrong. If previous errors, then just remove the
1071 -- identifier and continue, otherwise raise an exception.
1073 if No (Ent) then
1074 Check_Error_Detected;
1075 Set_Identifier (N, Empty);
1077 else
1078 Set_Ekind (Ent, E_Block);
1079 Generate_Reference (Ent, N, ' ');
1080 Generate_Definition (Ent);
1082 if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
1083 Set_Label_Construct (Parent (Ent), N);
1084 end if;
1085 end if;
1086 end if;
1088 -- If no entity set, create a label entity
1090 if No (Ent) then
1091 Ent := New_Internal_Entity (E_Block, Current_Scope, Sloc (N), 'B');
1092 Set_Identifier (N, New_Occurrence_Of (Ent, Sloc (N)));
1093 Set_Parent (Ent, N);
1094 end if;
1096 Set_Etype (Ent, Standard_Void_Type);
1097 Set_Block_Node (Ent, Identifier (N));
1098 Push_Scope (Ent);
1100 -- The block served as an extended return statement. Ensure that any
1101 -- entities created during the analysis and expansion of the return
1102 -- object declaration are once again visible.
1104 if Is_BIP_Return_Statement then
1105 Install_Return_Entities (Ent);
1106 end if;
1108 if Present (Decls) then
1109 Analyze_Declarations (Decls);
1110 Check_Completion;
1111 Inspect_Deferred_Constant_Completion (Decls);
1112 end if;
1114 Analyze (HSS);
1115 Process_End_Label (HSS, 'e', Ent);
1117 -- If exception handlers are present, then we indicate that enclosing
1118 -- scopes contain a block with handlers. We only need to mark non-
1119 -- generic scopes.
1121 if Present (EH) then
1122 S := Scope (Ent);
1123 loop
1124 Set_Has_Nested_Block_With_Handler (S);
1125 exit when Is_Overloadable (S)
1126 or else Ekind (S) = E_Package
1127 or else Is_Generic_Unit (S);
1128 S := Scope (S);
1129 end loop;
1130 end if;
1132 Check_References (Ent);
1133 End_Scope;
1135 if Unblocked_Exit_Count = 0 then
1136 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1137 Check_Unreachable_Code (N);
1138 else
1139 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1140 end if;
1141 end;
1142 end Analyze_Block_Statement;
1144 --------------------------------
1145 -- Analyze_Compound_Statement --
1146 --------------------------------
1148 procedure Analyze_Compound_Statement (N : Node_Id) is
1149 begin
1150 Analyze_List (Actions (N));
1151 end Analyze_Compound_Statement;
1153 ----------------------------
1154 -- Analyze_Case_Statement --
1155 ----------------------------
1157 procedure Analyze_Case_Statement (N : Node_Id) is
1158 Exp : Node_Id;
1159 Exp_Type : Entity_Id;
1160 Exp_Btype : Entity_Id;
1161 Last_Choice : Nat;
1163 Others_Present : Boolean;
1164 -- Indicates if Others was present
1166 pragma Warnings (Off, Last_Choice);
1167 -- Don't care about assigned value
1169 Statements_Analyzed : Boolean := False;
1170 -- Set True if at least some statement sequences get analyzed. If False
1171 -- on exit, means we had a serious error that prevented full analysis of
1172 -- the case statement, and as a result it is not a good idea to output
1173 -- warning messages about unreachable code.
1175 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1176 -- Recursively save value of this global, will be restored on exit
1178 procedure Non_Static_Choice_Error (Choice : Node_Id);
1179 -- Error routine invoked by the generic instantiation below when the
1180 -- case statement has a non static choice.
1182 procedure Process_Statements (Alternative : Node_Id);
1183 -- Analyzes the statements associated with a case alternative. Needed
1184 -- by instantiation below.
1186 package Analyze_Case_Choices is new
1187 Generic_Analyze_Choices
1188 (Process_Associated_Node => Process_Statements);
1189 use Analyze_Case_Choices;
1190 -- Instantiation of the generic choice analysis package
1192 package Check_Case_Choices is new
1193 Generic_Check_Choices
1194 (Process_Empty_Choice => No_OP,
1195 Process_Non_Static_Choice => Non_Static_Choice_Error,
1196 Process_Associated_Node => No_OP);
1197 use Check_Case_Choices;
1198 -- Instantiation of the generic choice processing package
1200 -----------------------------
1201 -- Non_Static_Choice_Error --
1202 -----------------------------
1204 procedure Non_Static_Choice_Error (Choice : Node_Id) is
1205 begin
1206 Flag_Non_Static_Expr
1207 ("choice given in case statement is not static!", Choice);
1208 end Non_Static_Choice_Error;
1210 ------------------------
1211 -- Process_Statements --
1212 ------------------------
1214 procedure Process_Statements (Alternative : Node_Id) is
1215 Choices : constant List_Id := Discrete_Choices (Alternative);
1216 Ent : Entity_Id;
1218 begin
1219 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1220 Statements_Analyzed := True;
1222 -- An interesting optimization. If the case statement expression
1223 -- is a simple entity, then we can set the current value within an
1224 -- alternative if the alternative has one possible value.
1226 -- case N is
1227 -- when 1 => alpha
1228 -- when 2 | 3 => beta
1229 -- when others => gamma
1231 -- Here we know that N is initially 1 within alpha, but for beta and
1232 -- gamma, we do not know anything more about the initial value.
1234 if Is_Entity_Name (Exp) then
1235 Ent := Entity (Exp);
1237 if Ekind_In (Ent, E_Variable,
1238 E_In_Out_Parameter,
1239 E_Out_Parameter)
1240 then
1241 if List_Length (Choices) = 1
1242 and then Nkind (First (Choices)) in N_Subexpr
1243 and then Compile_Time_Known_Value (First (Choices))
1244 then
1245 Set_Current_Value (Entity (Exp), First (Choices));
1246 end if;
1248 Analyze_Statements (Statements (Alternative));
1250 -- After analyzing the case, set the current value to empty
1251 -- since we won't know what it is for the next alternative
1252 -- (unless reset by this same circuit), or after the case.
1254 Set_Current_Value (Entity (Exp), Empty);
1255 return;
1256 end if;
1257 end if;
1259 -- Case where expression is not an entity name of a variable
1261 Analyze_Statements (Statements (Alternative));
1262 end Process_Statements;
1264 -- Start of processing for Analyze_Case_Statement
1266 begin
1267 Unblocked_Exit_Count := 0;
1268 Exp := Expression (N);
1269 Analyze (Exp);
1271 -- The expression must be of any discrete type. In rare cases, the
1272 -- expander constructs a case statement whose expression has a private
1273 -- type whose full view is discrete. This can happen when generating
1274 -- a stream operation for a variant type after the type is frozen,
1275 -- when the partial of view of the type of the discriminant is private.
1276 -- In that case, use the full view to analyze case alternatives.
1278 if not Is_Overloaded (Exp)
1279 and then not Comes_From_Source (N)
1280 and then Is_Private_Type (Etype (Exp))
1281 and then Present (Full_View (Etype (Exp)))
1282 and then Is_Discrete_Type (Full_View (Etype (Exp)))
1283 then
1284 Resolve (Exp, Etype (Exp));
1285 Exp_Type := Full_View (Etype (Exp));
1287 else
1288 Analyze_And_Resolve (Exp, Any_Discrete);
1289 Exp_Type := Etype (Exp);
1290 end if;
1292 Check_Unset_Reference (Exp);
1293 Exp_Btype := Base_Type (Exp_Type);
1295 -- The expression must be of a discrete type which must be determinable
1296 -- independently of the context in which the expression occurs, but
1297 -- using the fact that the expression must be of a discrete type.
1298 -- Moreover, the type this expression must not be a character literal
1299 -- (which is always ambiguous) or, for Ada-83, a generic formal type.
1301 -- If error already reported by Resolve, nothing more to do
1303 if Exp_Btype = Any_Discrete or else Exp_Btype = Any_Type then
1304 return;
1306 elsif Exp_Btype = Any_Character then
1307 Error_Msg_N
1308 ("character literal as case expression is ambiguous", Exp);
1309 return;
1311 elsif Ada_Version = Ada_83
1312 and then (Is_Generic_Type (Exp_Btype)
1313 or else Is_Generic_Type (Root_Type (Exp_Btype)))
1314 then
1315 Error_Msg_N
1316 ("(Ada 83) case expression cannot be of a generic type", Exp);
1317 return;
1318 end if;
1320 -- If the case expression is a formal object of mode in out, then treat
1321 -- it as having a nonstatic subtype by forcing use of the base type
1322 -- (which has to get passed to Check_Case_Choices below). Also use base
1323 -- type when the case expression is parenthesized.
1325 if Paren_Count (Exp) > 0
1326 or else (Is_Entity_Name (Exp)
1327 and then Ekind (Entity (Exp)) = E_Generic_In_Out_Parameter)
1328 then
1329 Exp_Type := Exp_Btype;
1330 end if;
1332 -- Call instantiated procedures to analyzwe and check discrete choices
1334 Analyze_Choices (Alternatives (N), Exp_Type);
1335 Check_Choices (N, Alternatives (N), Exp_Type, Others_Present);
1337 -- Case statement with single OTHERS alternative not allowed in SPARK
1339 if Others_Present and then List_Length (Alternatives (N)) = 1 then
1340 Check_SPARK_05_Restriction
1341 ("OTHERS as unique case alternative is not allowed", N);
1342 end if;
1344 if Exp_Type = Universal_Integer and then not Others_Present then
1345 Error_Msg_N ("case on universal integer requires OTHERS choice", Exp);
1346 end if;
1348 -- If all our exits were blocked by unconditional transfers of control,
1349 -- then the entire CASE statement acts as an unconditional transfer of
1350 -- control, so treat it like one, and check unreachable code. Skip this
1351 -- test if we had serious errors preventing any statement analysis.
1353 if Unblocked_Exit_Count = 0 and then Statements_Analyzed then
1354 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1355 Check_Unreachable_Code (N);
1356 else
1357 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1358 end if;
1360 -- If the expander is active it will detect the case of a statically
1361 -- determined single alternative and remove warnings for the case, but
1362 -- if we are not doing expansion, that circuit won't be active. Here we
1363 -- duplicate the effect of removing warnings in the same way, so that
1364 -- we will get the same set of warnings in -gnatc mode.
1366 if not Expander_Active
1367 and then Compile_Time_Known_Value (Expression (N))
1368 and then Serious_Errors_Detected = 0
1369 then
1370 declare
1371 Chosen : constant Node_Id := Find_Static_Alternative (N);
1372 Alt : Node_Id;
1374 begin
1375 Alt := First (Alternatives (N));
1376 while Present (Alt) loop
1377 if Alt /= Chosen then
1378 Remove_Warning_Messages (Statements (Alt));
1379 end if;
1381 Next (Alt);
1382 end loop;
1383 end;
1384 end if;
1385 end Analyze_Case_Statement;
1387 ----------------------------
1388 -- Analyze_Exit_Statement --
1389 ----------------------------
1391 -- If the exit includes a name, it must be the name of a currently open
1392 -- loop. Otherwise there must be an innermost open loop on the stack, to
1393 -- which the statement implicitly refers.
1395 -- Additionally, in SPARK mode:
1397 -- The exit can only name the closest enclosing loop;
1399 -- An exit with a when clause must be directly contained in a loop;
1401 -- An exit without a when clause must be directly contained in an
1402 -- if-statement with no elsif or else, which is itself directly contained
1403 -- in a loop. The exit must be the last statement in the if-statement.
1405 procedure Analyze_Exit_Statement (N : Node_Id) is
1406 Target : constant Node_Id := Name (N);
1407 Cond : constant Node_Id := Condition (N);
1408 Scope_Id : Entity_Id := Empty; -- initialize to prevent warning
1409 U_Name : Entity_Id;
1410 Kind : Entity_Kind;
1412 begin
1413 if No (Cond) then
1414 Check_Unreachable_Code (N);
1415 end if;
1417 if Present (Target) then
1418 Analyze (Target);
1419 U_Name := Entity (Target);
1421 if not In_Open_Scopes (U_Name) or else Ekind (U_Name) /= E_Loop then
1422 Error_Msg_N ("invalid loop name in exit statement", N);
1423 return;
1425 else
1426 if Has_Loop_In_Inner_Open_Scopes (U_Name) then
1427 Check_SPARK_05_Restriction
1428 ("exit label must name the closest enclosing loop", N);
1429 end if;
1431 Set_Has_Exit (U_Name);
1432 end if;
1434 else
1435 U_Name := Empty;
1436 end if;
1438 for J in reverse 0 .. Scope_Stack.Last loop
1439 Scope_Id := Scope_Stack.Table (J).Entity;
1440 Kind := Ekind (Scope_Id);
1442 if Kind = E_Loop and then (No (Target) or else Scope_Id = U_Name) then
1443 Set_Has_Exit (Scope_Id);
1444 exit;
1446 elsif Kind = E_Block
1447 or else Kind = E_Loop
1448 or else Kind = E_Return_Statement
1449 then
1450 null;
1452 else
1453 Error_Msg_N
1454 ("cannot exit from program unit or accept statement", N);
1455 return;
1456 end if;
1457 end loop;
1459 -- Verify that if present the condition is a Boolean expression
1461 if Present (Cond) then
1462 Analyze_And_Resolve (Cond, Any_Boolean);
1463 Check_Unset_Reference (Cond);
1464 end if;
1466 -- In SPARK mode, verify that the exit statement respects the SPARK
1467 -- restrictions.
1469 if Present (Cond) then
1470 if Nkind (Parent (N)) /= N_Loop_Statement then
1471 Check_SPARK_05_Restriction
1472 ("exit with when clause must be directly in loop", N);
1473 end if;
1475 else
1476 if Nkind (Parent (N)) /= N_If_Statement then
1477 if Nkind (Parent (N)) = N_Elsif_Part then
1478 Check_SPARK_05_Restriction
1479 ("exit must be in IF without ELSIF", N);
1480 else
1481 Check_SPARK_05_Restriction ("exit must be directly in IF", N);
1482 end if;
1484 elsif Nkind (Parent (Parent (N))) /= N_Loop_Statement then
1485 Check_SPARK_05_Restriction
1486 ("exit must be in IF directly in loop", N);
1488 -- First test the presence of ELSE, so that an exit in an ELSE leads
1489 -- to an error mentioning the ELSE.
1491 elsif Present (Else_Statements (Parent (N))) then
1492 Check_SPARK_05_Restriction ("exit must be in IF without ELSE", N);
1494 -- An exit in an ELSIF does not reach here, as it would have been
1495 -- detected in the case (Nkind (Parent (N)) /= N_If_Statement).
1497 elsif Present (Elsif_Parts (Parent (N))) then
1498 Check_SPARK_05_Restriction ("exit must be in IF without ELSIF", N);
1499 end if;
1500 end if;
1502 -- Chain exit statement to associated loop entity
1504 Set_Next_Exit_Statement (N, First_Exit_Statement (Scope_Id));
1505 Set_First_Exit_Statement (Scope_Id, N);
1507 -- Since the exit may take us out of a loop, any previous assignment
1508 -- statement is not useless, so clear last assignment indications. It
1509 -- is OK to keep other current values, since if the exit statement
1510 -- does not exit, then the current values are still valid.
1512 Kill_Current_Values (Last_Assignment_Only => True);
1513 end Analyze_Exit_Statement;
1515 ----------------------------
1516 -- Analyze_Goto_Statement --
1517 ----------------------------
1519 procedure Analyze_Goto_Statement (N : Node_Id) is
1520 Label : constant Node_Id := Name (N);
1521 Scope_Id : Entity_Id;
1522 Label_Scope : Entity_Id;
1523 Label_Ent : Entity_Id;
1525 begin
1526 Check_SPARK_05_Restriction ("goto statement is not allowed", N);
1528 -- Actual semantic checks
1530 Check_Unreachable_Code (N);
1531 Kill_Current_Values (Last_Assignment_Only => True);
1533 Analyze (Label);
1534 Label_Ent := Entity (Label);
1536 -- Ignore previous error
1538 if Label_Ent = Any_Id then
1539 Check_Error_Detected;
1540 return;
1542 -- We just have a label as the target of a goto
1544 elsif Ekind (Label_Ent) /= E_Label then
1545 Error_Msg_N ("target of goto statement must be a label", Label);
1546 return;
1548 -- Check that the target of the goto is reachable according to Ada
1549 -- scoping rules. Note: the special gotos we generate for optimizing
1550 -- local handling of exceptions would violate these rules, but we mark
1551 -- such gotos as analyzed when built, so this code is never entered.
1553 elsif not Reachable (Label_Ent) then
1554 Error_Msg_N ("target of goto statement is not reachable", Label);
1555 return;
1556 end if;
1558 -- Here if goto passes initial validity checks
1560 Label_Scope := Enclosing_Scope (Label_Ent);
1562 for J in reverse 0 .. Scope_Stack.Last loop
1563 Scope_Id := Scope_Stack.Table (J).Entity;
1565 if Label_Scope = Scope_Id
1566 or else not Ekind_In (Scope_Id, E_Block, E_Loop, E_Return_Statement)
1567 then
1568 if Scope_Id /= Label_Scope then
1569 Error_Msg_N
1570 ("cannot exit from program unit or accept statement", N);
1571 end if;
1573 return;
1574 end if;
1575 end loop;
1577 raise Program_Error;
1578 end Analyze_Goto_Statement;
1580 --------------------------
1581 -- Analyze_If_Statement --
1582 --------------------------
1584 -- A special complication arises in the analysis of if statements
1586 -- The expander has circuitry to completely delete code that it can tell
1587 -- will not be executed (as a result of compile time known conditions). In
1588 -- the analyzer, we ensure that code that will be deleted in this manner
1589 -- is analyzed but not expanded. This is obviously more efficient, but
1590 -- more significantly, difficulties arise if code is expanded and then
1591 -- eliminated (e.g. exception table entries disappear). Similarly, itypes
1592 -- generated in deleted code must be frozen from start, because the nodes
1593 -- on which they depend will not be available at the freeze point.
1595 procedure Analyze_If_Statement (N : Node_Id) is
1596 E : Node_Id;
1598 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1599 -- Recursively save value of this global, will be restored on exit
1601 Save_In_Deleted_Code : Boolean;
1603 Del : Boolean := False;
1604 -- This flag gets set True if a True condition has been found, which
1605 -- means that remaining ELSE/ELSIF parts are deleted.
1607 procedure Analyze_Cond_Then (Cnode : Node_Id);
1608 -- This is applied to either the N_If_Statement node itself or to an
1609 -- N_Elsif_Part node. It deals with analyzing the condition and the THEN
1610 -- statements associated with it.
1612 -----------------------
1613 -- Analyze_Cond_Then --
1614 -----------------------
1616 procedure Analyze_Cond_Then (Cnode : Node_Id) is
1617 Cond : constant Node_Id := Condition (Cnode);
1618 Tstm : constant List_Id := Then_Statements (Cnode);
1620 begin
1621 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1622 Analyze_And_Resolve (Cond, Any_Boolean);
1623 Check_Unset_Reference (Cond);
1624 Set_Current_Value_Condition (Cnode);
1626 -- If already deleting, then just analyze then statements
1628 if Del then
1629 Analyze_Statements (Tstm);
1631 -- Compile time known value, not deleting yet
1633 elsif Compile_Time_Known_Value (Cond) then
1634 Save_In_Deleted_Code := In_Deleted_Code;
1636 -- If condition is True, then analyze the THEN statements and set
1637 -- no expansion for ELSE and ELSIF parts.
1639 if Is_True (Expr_Value (Cond)) then
1640 Analyze_Statements (Tstm);
1641 Del := True;
1642 Expander_Mode_Save_And_Set (False);
1643 In_Deleted_Code := True;
1645 -- If condition is False, analyze THEN with expansion off
1647 else -- Is_False (Expr_Value (Cond))
1648 Expander_Mode_Save_And_Set (False);
1649 In_Deleted_Code := True;
1650 Analyze_Statements (Tstm);
1651 Expander_Mode_Restore;
1652 In_Deleted_Code := Save_In_Deleted_Code;
1653 end if;
1655 -- Not known at compile time, not deleting, normal analysis
1657 else
1658 Analyze_Statements (Tstm);
1659 end if;
1660 end Analyze_Cond_Then;
1662 -- Start of processing for Analyze_If_Statement
1664 begin
1665 -- Initialize exit count for else statements. If there is no else part,
1666 -- this count will stay non-zero reflecting the fact that the uncovered
1667 -- else case is an unblocked exit.
1669 Unblocked_Exit_Count := 1;
1670 Analyze_Cond_Then (N);
1672 -- Now to analyze the elsif parts if any are present
1674 if Present (Elsif_Parts (N)) then
1675 E := First (Elsif_Parts (N));
1676 while Present (E) loop
1677 Analyze_Cond_Then (E);
1678 Next (E);
1679 end loop;
1680 end if;
1682 if Present (Else_Statements (N)) then
1683 Analyze_Statements (Else_Statements (N));
1684 end if;
1686 -- If all our exits were blocked by unconditional transfers of control,
1687 -- then the entire IF statement acts as an unconditional transfer of
1688 -- control, so treat it like one, and check unreachable code.
1690 if Unblocked_Exit_Count = 0 then
1691 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1692 Check_Unreachable_Code (N);
1693 else
1694 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1695 end if;
1697 if Del then
1698 Expander_Mode_Restore;
1699 In_Deleted_Code := Save_In_Deleted_Code;
1700 end if;
1702 if not Expander_Active
1703 and then Compile_Time_Known_Value (Condition (N))
1704 and then Serious_Errors_Detected = 0
1705 then
1706 if Is_True (Expr_Value (Condition (N))) then
1707 Remove_Warning_Messages (Else_Statements (N));
1709 if Present (Elsif_Parts (N)) then
1710 E := First (Elsif_Parts (N));
1711 while Present (E) loop
1712 Remove_Warning_Messages (Then_Statements (E));
1713 Next (E);
1714 end loop;
1715 end if;
1717 else
1718 Remove_Warning_Messages (Then_Statements (N));
1719 end if;
1720 end if;
1722 -- Warn on redundant if statement that has no effect
1724 -- Note, we could also check empty ELSIF parts ???
1726 if Warn_On_Redundant_Constructs
1728 -- If statement must be from source
1730 and then Comes_From_Source (N)
1732 -- Condition must not have obvious side effect
1734 and then Has_No_Obvious_Side_Effects (Condition (N))
1736 -- No elsif parts of else part
1738 and then No (Elsif_Parts (N))
1739 and then No (Else_Statements (N))
1741 -- Then must be a single null statement
1743 and then List_Length (Then_Statements (N)) = 1
1744 then
1745 -- Go to original node, since we may have rewritten something as
1746 -- a null statement (e.g. a case we could figure the outcome of).
1748 declare
1749 T : constant Node_Id := First (Then_Statements (N));
1750 S : constant Node_Id := Original_Node (T);
1752 begin
1753 if Comes_From_Source (S) and then Nkind (S) = N_Null_Statement then
1754 Error_Msg_N ("if statement has no effect?r?", N);
1755 end if;
1756 end;
1757 end if;
1758 end Analyze_If_Statement;
1760 ----------------------------------------
1761 -- Analyze_Implicit_Label_Declaration --
1762 ----------------------------------------
1764 -- An implicit label declaration is generated in the innermost enclosing
1765 -- declarative part. This is done for labels, and block and loop names.
1767 -- Note: any changes in this routine may need to be reflected in
1768 -- Analyze_Label_Entity.
1770 procedure Analyze_Implicit_Label_Declaration (N : Node_Id) is
1771 Id : constant Node_Id := Defining_Identifier (N);
1772 begin
1773 Enter_Name (Id);
1774 Set_Ekind (Id, E_Label);
1775 Set_Etype (Id, Standard_Void_Type);
1776 Set_Enclosing_Scope (Id, Current_Scope);
1777 end Analyze_Implicit_Label_Declaration;
1779 ------------------------------
1780 -- Analyze_Iteration_Scheme --
1781 ------------------------------
1783 procedure Analyze_Iteration_Scheme (N : Node_Id) is
1784 Cond : Node_Id;
1785 Iter_Spec : Node_Id;
1786 Loop_Spec : Node_Id;
1788 begin
1789 -- For an infinite loop, there is no iteration scheme
1791 if No (N) then
1792 return;
1793 end if;
1795 Cond := Condition (N);
1796 Iter_Spec := Iterator_Specification (N);
1797 Loop_Spec := Loop_Parameter_Specification (N);
1799 if Present (Cond) then
1800 Analyze_And_Resolve (Cond, Any_Boolean);
1801 Check_Unset_Reference (Cond);
1802 Set_Current_Value_Condition (N);
1804 elsif Present (Iter_Spec) then
1805 Analyze_Iterator_Specification (Iter_Spec);
1807 else
1808 Analyze_Loop_Parameter_Specification (Loop_Spec);
1809 end if;
1810 end Analyze_Iteration_Scheme;
1812 ------------------------------------
1813 -- Analyze_Iterator_Specification --
1814 ------------------------------------
1816 procedure Analyze_Iterator_Specification (N : Node_Id) is
1817 procedure Check_Reverse_Iteration (Typ : Entity_Id);
1818 -- For an iteration over a container, if the loop carries the Reverse
1819 -- indicator, verify that the container type has an Iterate aspect that
1820 -- implements the reversible iterator interface.
1822 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id;
1823 -- For containers with Iterator and related aspects, the cursor is
1824 -- obtained by locating an entity with the proper name in the scope
1825 -- of the type.
1827 -----------------------------
1828 -- Check_Reverse_Iteration --
1829 -----------------------------
1831 procedure Check_Reverse_Iteration (Typ : Entity_Id) is
1832 begin
1833 if Reverse_Present (N)
1834 and then not Is_Array_Type (Typ)
1835 and then not Is_Reversible_Iterator (Typ)
1836 then
1837 Error_Msg_NE
1838 ("container type does not support reverse iteration", N, Typ);
1839 end if;
1840 end Check_Reverse_Iteration;
1842 ---------------------
1843 -- Get_Cursor_Type --
1844 ---------------------
1846 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id is
1847 Ent : Entity_Id;
1849 begin
1850 -- If iterator type is derived, the cursor is declared in the scope
1851 -- of the parent type.
1853 if Is_Derived_Type (Typ) then
1854 Ent := First_Entity (Scope (Etype (Typ)));
1855 else
1856 Ent := First_Entity (Scope (Typ));
1857 end if;
1859 while Present (Ent) loop
1860 exit when Chars (Ent) = Name_Cursor;
1861 Next_Entity (Ent);
1862 end loop;
1864 if No (Ent) then
1865 return Any_Type;
1866 end if;
1868 -- The cursor is the target of generated assignments in the
1869 -- loop, and cannot have a limited type.
1871 if Is_Limited_Type (Etype (Ent)) then
1872 Error_Msg_N ("cursor type cannot be limited", N);
1873 end if;
1875 return Etype (Ent);
1876 end Get_Cursor_Type;
1878 -- Local variables
1880 Def_Id : constant Node_Id := Defining_Identifier (N);
1881 Iter_Name : constant Node_Id := Name (N);
1882 Loc : constant Source_Ptr := Sloc (N);
1883 Subt : constant Node_Id := Subtype_Indication (N);
1885 Bas : Entity_Id := Empty; -- initialize to prevent warning
1886 Typ : Entity_Id;
1888 -- Start of processing for Analyze_Iterator_Specification
1890 begin
1891 Enter_Name (Def_Id);
1893 -- AI12-0151 specifies that when the subtype indication is present, it
1894 -- must statically match the type of the array or container element.
1895 -- To simplify this check, we introduce a subtype declaration with the
1896 -- given subtype indication when it carries a constraint, and rewrite
1897 -- the original as a reference to the created subtype entity.
1899 if Present (Subt) then
1900 if Nkind (Subt) = N_Subtype_Indication then
1901 declare
1902 S : constant Entity_Id := Make_Temporary (Sloc (Subt), 'S');
1903 Decl : constant Node_Id :=
1904 Make_Subtype_Declaration (Loc,
1905 Defining_Identifier => S,
1906 Subtype_Indication => New_Copy_Tree (Subt));
1907 begin
1908 Insert_Before (Parent (Parent (N)), Decl);
1909 Analyze (Decl);
1910 Rewrite (Subt, New_Occurrence_Of (S, Sloc (Subt)));
1911 end;
1912 else
1913 Analyze (Subt);
1914 end if;
1916 -- Save entity of subtype indication for subsequent check
1918 Bas := Entity (Subt);
1919 end if;
1921 Preanalyze_Range (Iter_Name);
1923 -- Set the kind of the loop variable, which is not visible within the
1924 -- iterator name.
1926 Set_Ekind (Def_Id, E_Variable);
1928 -- Provide a link between the iterator variable and the container, for
1929 -- subsequent use in cross-reference and modification information.
1931 if Of_Present (N) then
1932 Set_Related_Expression (Def_Id, Iter_Name);
1934 -- For a container, the iterator is specified through the aspect
1936 if not Is_Array_Type (Etype (Iter_Name)) then
1937 declare
1938 Iterator : constant Entity_Id :=
1939 Find_Value_Of_Aspect
1940 (Etype (Iter_Name), Aspect_Default_Iterator);
1942 I : Interp_Index;
1943 It : Interp;
1945 begin
1946 if No (Iterator) then
1947 null; -- error reported below.
1949 elsif not Is_Overloaded (Iterator) then
1950 Check_Reverse_Iteration (Etype (Iterator));
1952 -- If Iterator is overloaded, use reversible iterator if
1953 -- one is available.
1955 elsif Is_Overloaded (Iterator) then
1956 Get_First_Interp (Iterator, I, It);
1957 while Present (It.Nam) loop
1958 if Ekind (It.Nam) = E_Function
1959 and then Is_Reversible_Iterator (Etype (It.Nam))
1960 then
1961 Set_Etype (Iterator, It.Typ);
1962 Set_Entity (Iterator, It.Nam);
1963 exit;
1964 end if;
1966 Get_Next_Interp (I, It);
1967 end loop;
1969 Check_Reverse_Iteration (Etype (Iterator));
1970 end if;
1971 end;
1972 end if;
1973 end if;
1975 -- If the domain of iteration is an expression, create a declaration for
1976 -- it, so that finalization actions are introduced outside of the loop.
1977 -- The declaration must be a renaming because the body of the loop may
1978 -- assign to elements.
1980 if not Is_Entity_Name (Iter_Name)
1982 -- When the context is a quantified expression, the renaming
1983 -- declaration is delayed until the expansion phase if we are
1984 -- doing expansion.
1986 and then (Nkind (Parent (N)) /= N_Quantified_Expression
1987 or else Operating_Mode = Check_Semantics)
1989 -- Do not perform this expansion for ASIS and when expansion is
1990 -- disabled, where the temporary may hide the transformation of a
1991 -- selected component into a prefixed function call, and references
1992 -- need to see the original expression.
1994 and then Expander_Active
1995 then
1996 declare
1997 Id : constant Entity_Id := Make_Temporary (Loc, 'R', Iter_Name);
1998 Decl : Node_Id;
1999 Act_S : Node_Id;
2001 begin
2003 -- If the domain of iteration is an array component that depends
2004 -- on a discriminant, create actual subtype for it. Pre-analysis
2005 -- does not generate the actual subtype of a selected component.
2007 if Nkind (Iter_Name) = N_Selected_Component
2008 and then Is_Array_Type (Etype (Iter_Name))
2009 then
2010 Act_S :=
2011 Build_Actual_Subtype_Of_Component
2012 (Etype (Selector_Name (Iter_Name)), Iter_Name);
2013 Insert_Action (N, Act_S);
2015 if Present (Act_S) then
2016 Typ := Defining_Identifier (Act_S);
2017 else
2018 Typ := Etype (Iter_Name);
2019 end if;
2021 else
2022 Typ := Etype (Iter_Name);
2024 -- Verify that the expression produces an iterator
2026 if not Of_Present (N) and then not Is_Iterator (Typ)
2027 and then not Is_Array_Type (Typ)
2028 and then No (Find_Aspect (Typ, Aspect_Iterable))
2029 then
2030 Error_Msg_N
2031 ("expect object that implements iterator interface",
2032 Iter_Name);
2033 end if;
2034 end if;
2036 -- Protect against malformed iterator
2038 if Typ = Any_Type then
2039 Error_Msg_N ("invalid expression in loop iterator", Iter_Name);
2040 return;
2041 end if;
2043 if not Of_Present (N) then
2044 Check_Reverse_Iteration (Typ);
2045 end if;
2047 -- The name in the renaming declaration may be a function call.
2048 -- Indicate that it does not come from source, to suppress
2049 -- spurious warnings on renamings of parameterless functions,
2050 -- a common enough idiom in user-defined iterators.
2052 Decl :=
2053 Make_Object_Renaming_Declaration (Loc,
2054 Defining_Identifier => Id,
2055 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
2056 Name =>
2057 New_Copy_Tree (Iter_Name, New_Sloc => Loc));
2059 Insert_Actions (Parent (Parent (N)), New_List (Decl));
2060 Rewrite (Name (N), New_Occurrence_Of (Id, Loc));
2061 Set_Etype (Id, Typ);
2062 Set_Etype (Name (N), Typ);
2063 end;
2065 -- Container is an entity or an array with uncontrolled components, or
2066 -- else it is a container iterator given by a function call, typically
2067 -- called Iterate in the case of predefined containers, even though
2068 -- Iterate is not a reserved name. What matters is that the return type
2069 -- of the function is an iterator type.
2071 elsif Is_Entity_Name (Iter_Name) then
2072 Analyze (Iter_Name);
2074 if Nkind (Iter_Name) = N_Function_Call then
2075 declare
2076 C : constant Node_Id := Name (Iter_Name);
2077 I : Interp_Index;
2078 It : Interp;
2080 begin
2081 if not Is_Overloaded (Iter_Name) then
2082 Resolve (Iter_Name, Etype (C));
2084 else
2085 Get_First_Interp (C, I, It);
2086 while It.Typ /= Empty loop
2087 if Reverse_Present (N) then
2088 if Is_Reversible_Iterator (It.Typ) then
2089 Resolve (Iter_Name, It.Typ);
2090 exit;
2091 end if;
2093 elsif Is_Iterator (It.Typ) then
2094 Resolve (Iter_Name, It.Typ);
2095 exit;
2096 end if;
2098 Get_Next_Interp (I, It);
2099 end loop;
2100 end if;
2101 end;
2103 -- Domain of iteration is not overloaded
2105 else
2106 Resolve (Iter_Name, Etype (Iter_Name));
2107 end if;
2109 if not Of_Present (N) then
2110 Check_Reverse_Iteration (Etype (Iter_Name));
2111 end if;
2112 end if;
2114 -- Get base type of container, for proper retrieval of Cursor type
2115 -- and primitive operations.
2117 Typ := Base_Type (Etype (Iter_Name));
2119 if Is_Array_Type (Typ) then
2120 if Of_Present (N) then
2121 Set_Etype (Def_Id, Component_Type (Typ));
2123 -- The loop variable is aliased if the array components are
2124 -- aliased.
2126 Set_Is_Aliased (Def_Id, Has_Aliased_Components (Typ));
2128 -- AI12-0047 stipulates that the domain (array or container)
2129 -- cannot be a component that depends on a discriminant if the
2130 -- enclosing object is mutable, to prevent a modification of the
2131 -- dowmain of iteration in the course of an iteration.
2133 -- If the object is an expression it has been captured in a
2134 -- temporary, so examine original node.
2136 if Nkind (Original_Node (Iter_Name)) = N_Selected_Component
2137 and then Is_Dependent_Component_Of_Mutable_Object
2138 (Original_Node (Iter_Name))
2139 then
2140 Error_Msg_N
2141 ("iterable name cannot be a discriminant-dependent "
2142 & "component of a mutable object", N);
2143 end if;
2145 if Present (Subt)
2146 and then
2147 (Base_Type (Bas) /= Base_Type (Component_Type (Typ))
2148 or else
2149 not Subtypes_Statically_Match (Bas, Component_Type (Typ)))
2150 then
2151 Error_Msg_N
2152 ("subtype indication does not match component type", Subt);
2153 end if;
2155 -- Here we have a missing Range attribute
2157 else
2158 Error_Msg_N
2159 ("missing Range attribute in iteration over an array", N);
2161 -- In Ada 2012 mode, this may be an attempt at an iterator
2163 if Ada_Version >= Ada_2012 then
2164 Error_Msg_NE
2165 ("\if& is meant to designate an element of the array, use OF",
2166 N, Def_Id);
2167 end if;
2169 -- Prevent cascaded errors
2171 Set_Ekind (Def_Id, E_Loop_Parameter);
2172 Set_Etype (Def_Id, Etype (First_Index (Typ)));
2173 end if;
2175 -- Check for type error in iterator
2177 elsif Typ = Any_Type then
2178 return;
2180 -- Iteration over a container
2182 else
2183 Set_Ekind (Def_Id, E_Loop_Parameter);
2184 Error_Msg_Ada_2012_Feature ("container iterator", Sloc (N));
2186 -- OF present
2188 if Of_Present (N) then
2189 if Has_Aspect (Typ, Aspect_Iterable) then
2190 declare
2191 Elt : constant Entity_Id :=
2192 Get_Iterable_Type_Primitive (Typ, Name_Element);
2193 begin
2194 if No (Elt) then
2195 Error_Msg_N
2196 ("missing Element primitive for iteration", N);
2197 else
2198 Set_Etype (Def_Id, Etype (Elt));
2199 end if;
2200 end;
2202 -- For a predefined container, The type of the loop variable is
2203 -- the Iterator_Element aspect of the container type.
2205 else
2206 declare
2207 Element : constant Entity_Id :=
2208 Find_Value_Of_Aspect
2209 (Typ, Aspect_Iterator_Element);
2210 Iterator : constant Entity_Id :=
2211 Find_Value_Of_Aspect
2212 (Typ, Aspect_Default_Iterator);
2213 Orig_Iter_Name : constant Node_Id :=
2214 Original_Node (Iter_Name);
2215 Cursor_Type : Entity_Id;
2217 begin
2218 if No (Element) then
2219 Error_Msg_NE ("cannot iterate over&", N, Typ);
2220 return;
2222 else
2223 Set_Etype (Def_Id, Entity (Element));
2224 Cursor_Type := Get_Cursor_Type (Typ);
2225 pragma Assert (Present (Cursor_Type));
2227 -- If subtype indication was given, verify that it covers
2228 -- the element type of the container.
2230 if Present (Subt)
2231 and then (not Covers (Bas, Etype (Def_Id))
2232 or else not Subtypes_Statically_Match
2233 (Bas, Etype (Def_Id)))
2234 then
2235 Error_Msg_N
2236 ("subtype indication does not match element type",
2237 Subt);
2238 end if;
2240 -- If the container has a variable indexing aspect, the
2241 -- element is a variable and is modifiable in the loop.
2243 if Has_Aspect (Typ, Aspect_Variable_Indexing) then
2244 Set_Ekind (Def_Id, E_Variable);
2245 end if;
2247 -- If the container is a constant, iterating over it
2248 -- requires a Constant_Indexing operation.
2250 if not Is_Variable (Iter_Name)
2251 and then not Has_Aspect (Typ, Aspect_Constant_Indexing)
2252 then
2253 Error_Msg_N
2254 ("iteration over constant container require "
2255 & "constant_indexing aspect", N);
2257 -- The Iterate function may have an in_out parameter,
2258 -- and a constant container is thus illegal.
2260 elsif Present (Iterator)
2261 and then Ekind (Entity (Iterator)) = E_Function
2262 and then Ekind (First_Formal (Entity (Iterator))) /=
2263 E_In_Parameter
2264 and then not Is_Variable (Iter_Name)
2265 then
2266 Error_Msg_N ("variable container expected", N);
2267 end if;
2269 -- Detect a case where the iterator denotes a component
2270 -- of a mutable object which depends on a discriminant.
2271 -- Note that the iterator may denote a function call in
2272 -- qualified form, in which case this check should not
2273 -- be performed.
2275 if Nkind (Orig_Iter_Name) = N_Selected_Component
2276 and then
2277 Present (Entity (Selector_Name (Orig_Iter_Name)))
2278 and then Ekind_In
2279 (Entity (Selector_Name (Orig_Iter_Name)),
2280 E_Component,
2281 E_Discriminant)
2282 and then Is_Dependent_Component_Of_Mutable_Object
2283 (Orig_Iter_Name)
2284 then
2285 Error_Msg_N
2286 ("container cannot be a discriminant-dependent "
2287 & "component of a mutable object", N);
2288 end if;
2289 end if;
2290 end;
2291 end if;
2293 -- IN iterator, domain is a range, or a call to Iterate function
2295 else
2296 -- For an iteration of the form IN, the name must denote an
2297 -- iterator, typically the result of a call to Iterate. Give a
2298 -- useful error message when the name is a container by itself.
2300 -- The type may be a formal container type, which has to have
2301 -- an Iterable aspect detailing the required primitives.
2303 if Is_Entity_Name (Original_Node (Name (N)))
2304 and then not Is_Iterator (Typ)
2305 then
2306 if Has_Aspect (Typ, Aspect_Iterable) then
2307 null;
2309 elsif not Has_Aspect (Typ, Aspect_Iterator_Element) then
2310 Error_Msg_NE
2311 ("cannot iterate over&", Name (N), Typ);
2312 else
2313 Error_Msg_N
2314 ("name must be an iterator, not a container", Name (N));
2315 end if;
2317 if Has_Aspect (Typ, Aspect_Iterable) then
2318 null;
2319 else
2320 Error_Msg_NE
2321 ("\to iterate directly over the elements of a container, "
2322 & "write `of &`", Name (N), Original_Node (Name (N)));
2324 -- No point in continuing analysis of iterator spec
2326 return;
2327 end if;
2328 end if;
2330 -- If the name is a call (typically prefixed) to some Iterate
2331 -- function, it has been rewritten as an object declaration.
2332 -- If that object is a selected component, verify that it is not
2333 -- a component of an unconstrained mutable object.
2335 if Nkind (Iter_Name) = N_Identifier
2336 or else (not Expander_Active and Comes_From_Source (Iter_Name))
2337 then
2338 declare
2339 Orig_Node : constant Node_Id := Original_Node (Iter_Name);
2340 Iter_Kind : constant Node_Kind := Nkind (Orig_Node);
2341 Obj : Node_Id;
2343 begin
2344 if Iter_Kind = N_Selected_Component then
2345 Obj := Prefix (Orig_Node);
2347 elsif Iter_Kind = N_Function_Call then
2348 Obj := First_Actual (Orig_Node);
2350 -- If neither, the name comes from source
2352 else
2353 Obj := Iter_Name;
2354 end if;
2356 if Nkind (Obj) = N_Selected_Component
2357 and then Is_Dependent_Component_Of_Mutable_Object (Obj)
2358 then
2359 Error_Msg_N
2360 ("container cannot be a discriminant-dependent "
2361 & "component of a mutable object", N);
2362 end if;
2363 end;
2364 end if;
2366 -- The result type of Iterate function is the classwide type of
2367 -- the interface parent. We need the specific Cursor type defined
2368 -- in the container package. We obtain it by name for a predefined
2369 -- container, or through the Iterable aspect for a formal one.
2371 if Has_Aspect (Typ, Aspect_Iterable) then
2372 Set_Etype (Def_Id,
2373 Get_Cursor_Type
2374 (Parent (Find_Value_Of_Aspect (Typ, Aspect_Iterable)),
2375 Typ));
2377 else
2378 Set_Etype (Def_Id, Get_Cursor_Type (Typ));
2379 Check_Reverse_Iteration (Etype (Iter_Name));
2380 end if;
2382 end if;
2383 end if;
2384 end Analyze_Iterator_Specification;
2386 -------------------
2387 -- Analyze_Label --
2388 -------------------
2390 -- Note: the semantic work required for analyzing labels (setting them as
2391 -- reachable) was done in a prepass through the statements in the block,
2392 -- so that forward gotos would be properly handled. See Analyze_Statements
2393 -- for further details. The only processing required here is to deal with
2394 -- optimizations that depend on an assumption of sequential control flow,
2395 -- since of course the occurrence of a label breaks this assumption.
2397 procedure Analyze_Label (N : Node_Id) is
2398 pragma Warnings (Off, N);
2399 begin
2400 Kill_Current_Values;
2401 end Analyze_Label;
2403 --------------------------
2404 -- Analyze_Label_Entity --
2405 --------------------------
2407 procedure Analyze_Label_Entity (E : Entity_Id) is
2408 begin
2409 Set_Ekind (E, E_Label);
2410 Set_Etype (E, Standard_Void_Type);
2411 Set_Enclosing_Scope (E, Current_Scope);
2412 Set_Reachable (E, True);
2413 end Analyze_Label_Entity;
2415 ------------------------------------------
2416 -- Analyze_Loop_Parameter_Specification --
2417 ------------------------------------------
2419 procedure Analyze_Loop_Parameter_Specification (N : Node_Id) is
2420 Loop_Nod : constant Node_Id := Parent (Parent (N));
2422 procedure Check_Controlled_Array_Attribute (DS : Node_Id);
2423 -- If the bounds are given by a 'Range reference on a function call
2424 -- that returns a controlled array, introduce an explicit declaration
2425 -- to capture the bounds, so that the function result can be finalized
2426 -- in timely fashion.
2428 procedure Check_Predicate_Use (T : Entity_Id);
2429 -- Diagnose Attempt to iterate through non-static predicate. Note that
2430 -- a type with inherited predicates may have both static and dynamic
2431 -- forms. In this case it is not sufficent to check the static predicate
2432 -- function only, look for a dynamic predicate aspect as well.
2434 function Has_Call_Using_Secondary_Stack (N : Node_Id) return Boolean;
2435 -- N is the node for an arbitrary construct. This function searches the
2436 -- construct N to see if any expressions within it contain function
2437 -- calls that use the secondary stack, returning True if any such call
2438 -- is found, and False otherwise.
2440 procedure Process_Bounds (R : Node_Id);
2441 -- If the iteration is given by a range, create temporaries and
2442 -- assignment statements block to capture the bounds and perform
2443 -- required finalization actions in case a bound includes a function
2444 -- call that uses the temporary stack. We first pre-analyze a copy of
2445 -- the range in order to determine the expected type, and analyze and
2446 -- resolve the original bounds.
2448 --------------------------------------
2449 -- Check_Controlled_Array_Attribute --
2450 --------------------------------------
2452 procedure Check_Controlled_Array_Attribute (DS : Node_Id) is
2453 begin
2454 if Nkind (DS) = N_Attribute_Reference
2455 and then Is_Entity_Name (Prefix (DS))
2456 and then Ekind (Entity (Prefix (DS))) = E_Function
2457 and then Is_Array_Type (Etype (Entity (Prefix (DS))))
2458 and then
2459 Is_Controlled (Component_Type (Etype (Entity (Prefix (DS)))))
2460 and then Expander_Active
2461 then
2462 declare
2463 Loc : constant Source_Ptr := Sloc (N);
2464 Arr : constant Entity_Id := Etype (Entity (Prefix (DS)));
2465 Indx : constant Entity_Id :=
2466 Base_Type (Etype (First_Index (Arr)));
2467 Subt : constant Entity_Id := Make_Temporary (Loc, 'S');
2468 Decl : Node_Id;
2470 begin
2471 Decl :=
2472 Make_Subtype_Declaration (Loc,
2473 Defining_Identifier => Subt,
2474 Subtype_Indication =>
2475 Make_Subtype_Indication (Loc,
2476 Subtype_Mark => New_Occurrence_Of (Indx, Loc),
2477 Constraint =>
2478 Make_Range_Constraint (Loc, Relocate_Node (DS))));
2479 Insert_Before (Loop_Nod, Decl);
2480 Analyze (Decl);
2482 Rewrite (DS,
2483 Make_Attribute_Reference (Loc,
2484 Prefix => New_Occurrence_Of (Subt, Loc),
2485 Attribute_Name => Attribute_Name (DS)));
2487 Analyze (DS);
2488 end;
2489 end if;
2490 end Check_Controlled_Array_Attribute;
2492 -------------------------
2493 -- Check_Predicate_Use --
2494 -------------------------
2496 procedure Check_Predicate_Use (T : Entity_Id) is
2497 begin
2498 -- A predicated subtype is illegal in loops and related constructs
2499 -- if the predicate is not static, or if it is a non-static subtype
2500 -- of a statically predicated subtype.
2502 if Is_Discrete_Type (T)
2503 and then Has_Predicates (T)
2504 and then (not Has_Static_Predicate (T)
2505 or else not Is_Static_Subtype (T)
2506 or else Has_Dynamic_Predicate_Aspect (T))
2507 then
2508 -- Seems a confusing message for the case of a static predicate
2509 -- with a non-static subtype???
2511 Bad_Predicated_Subtype_Use
2512 ("cannot use subtype& with non-static predicate for loop "
2513 & "iteration", Discrete_Subtype_Definition (N),
2514 T, Suggest_Static => True);
2516 elsif Inside_A_Generic
2517 and then Is_Generic_Formal (T)
2518 and then Is_Discrete_Type (T)
2519 then
2520 Set_No_Dynamic_Predicate_On_Actual (T);
2521 end if;
2522 end Check_Predicate_Use;
2524 ------------------------------------
2525 -- Has_Call_Using_Secondary_Stack --
2526 ------------------------------------
2528 function Has_Call_Using_Secondary_Stack (N : Node_Id) return Boolean is
2530 function Check_Call (N : Node_Id) return Traverse_Result;
2531 -- Check if N is a function call which uses the secondary stack
2533 ----------------
2534 -- Check_Call --
2535 ----------------
2537 function Check_Call (N : Node_Id) return Traverse_Result is
2538 Nam : Node_Id;
2539 Subp : Entity_Id;
2540 Return_Typ : Entity_Id;
2542 begin
2543 if Nkind (N) = N_Function_Call then
2544 Nam := Name (N);
2546 -- Call using access to subprogram with explicit dereference
2548 if Nkind (Nam) = N_Explicit_Dereference then
2549 Subp := Etype (Nam);
2551 -- Call using a selected component notation or Ada 2005 object
2552 -- operation notation
2554 elsif Nkind (Nam) = N_Selected_Component then
2555 Subp := Entity (Selector_Name (Nam));
2557 -- Common case
2559 else
2560 Subp := Entity (Nam);
2561 end if;
2563 Return_Typ := Etype (Subp);
2565 if Is_Composite_Type (Return_Typ)
2566 and then not Is_Constrained (Return_Typ)
2567 then
2568 return Abandon;
2570 elsif Sec_Stack_Needed_For_Return (Subp) then
2571 return Abandon;
2572 end if;
2573 end if;
2575 -- Continue traversing the tree
2577 return OK;
2578 end Check_Call;
2580 function Check_Calls is new Traverse_Func (Check_Call);
2582 -- Start of processing for Has_Call_Using_Secondary_Stack
2584 begin
2585 return Check_Calls (N) = Abandon;
2586 end Has_Call_Using_Secondary_Stack;
2588 --------------------
2589 -- Process_Bounds --
2590 --------------------
2592 procedure Process_Bounds (R : Node_Id) is
2593 Loc : constant Source_Ptr := Sloc (N);
2595 function One_Bound
2596 (Original_Bound : Node_Id;
2597 Analyzed_Bound : Node_Id;
2598 Typ : Entity_Id) return Node_Id;
2599 -- Capture value of bound and return captured value
2601 ---------------
2602 -- One_Bound --
2603 ---------------
2605 function One_Bound
2606 (Original_Bound : Node_Id;
2607 Analyzed_Bound : Node_Id;
2608 Typ : Entity_Id) return Node_Id
2610 Assign : Node_Id;
2611 Decl : Node_Id;
2612 Id : Entity_Id;
2614 begin
2615 -- If the bound is a constant or an object, no need for a separate
2616 -- declaration. If the bound is the result of previous expansion
2617 -- it is already analyzed and should not be modified. Note that
2618 -- the Bound will be resolved later, if needed, as part of the
2619 -- call to Make_Index (literal bounds may need to be resolved to
2620 -- type Integer).
2622 if Analyzed (Original_Bound) then
2623 return Original_Bound;
2625 elsif Nkind_In (Analyzed_Bound, N_Integer_Literal,
2626 N_Character_Literal)
2627 or else Is_Entity_Name (Analyzed_Bound)
2628 then
2629 Analyze_And_Resolve (Original_Bound, Typ);
2630 return Original_Bound;
2631 end if;
2633 -- Normally, the best approach is simply to generate a constant
2634 -- declaration that captures the bound. However, there is a nasty
2635 -- case where this is wrong. If the bound is complex, and has a
2636 -- possible use of the secondary stack, we need to generate a
2637 -- separate assignment statement to ensure the creation of a block
2638 -- which will release the secondary stack.
2640 -- We prefer the constant declaration, since it leaves us with a
2641 -- proper trace of the value, useful in optimizations that get rid
2642 -- of junk range checks.
2644 if not Has_Call_Using_Secondary_Stack (Analyzed_Bound) then
2645 Analyze_And_Resolve (Original_Bound, Typ);
2647 -- Ensure that the bound is valid. This check should not be
2648 -- generated when the range belongs to a quantified expression
2649 -- as the construct is still not expanded into its final form.
2651 if Nkind (Parent (R)) /= N_Loop_Parameter_Specification
2652 or else Nkind (Parent (Parent (R))) /= N_Quantified_Expression
2653 then
2654 Ensure_Valid (Original_Bound);
2655 end if;
2657 Force_Evaluation (Original_Bound);
2658 return Original_Bound;
2659 end if;
2661 Id := Make_Temporary (Loc, 'R', Original_Bound);
2663 -- Here we make a declaration with a separate assignment
2664 -- statement, and insert before loop header.
2666 Decl :=
2667 Make_Object_Declaration (Loc,
2668 Defining_Identifier => Id,
2669 Object_Definition => New_Occurrence_Of (Typ, Loc));
2671 Assign :=
2672 Make_Assignment_Statement (Loc,
2673 Name => New_Occurrence_Of (Id, Loc),
2674 Expression => Relocate_Node (Original_Bound));
2676 Insert_Actions (Loop_Nod, New_List (Decl, Assign));
2678 -- Now that this temporary variable is initialized we decorate it
2679 -- as safe-to-reevaluate to inform to the backend that no further
2680 -- asignment will be issued and hence it can be handled as side
2681 -- effect free. Note that this decoration must be done when the
2682 -- assignment has been analyzed because otherwise it will be
2683 -- rejected (see Analyze_Assignment).
2685 Set_Is_Safe_To_Reevaluate (Id);
2687 Rewrite (Original_Bound, New_Occurrence_Of (Id, Loc));
2689 if Nkind (Assign) = N_Assignment_Statement then
2690 return Expression (Assign);
2691 else
2692 return Original_Bound;
2693 end if;
2694 end One_Bound;
2696 Hi : constant Node_Id := High_Bound (R);
2697 Lo : constant Node_Id := Low_Bound (R);
2698 R_Copy : constant Node_Id := New_Copy_Tree (R);
2699 New_Hi : Node_Id;
2700 New_Lo : Node_Id;
2701 Typ : Entity_Id;
2703 -- Start of processing for Process_Bounds
2705 begin
2706 Set_Parent (R_Copy, Parent (R));
2707 Preanalyze_Range (R_Copy);
2708 Typ := Etype (R_Copy);
2710 -- If the type of the discrete range is Universal_Integer, then the
2711 -- bound's type must be resolved to Integer, and any object used to
2712 -- hold the bound must also have type Integer, unless the literal
2713 -- bounds are constant-folded expressions with a user-defined type.
2715 if Typ = Universal_Integer then
2716 if Nkind (Lo) = N_Integer_Literal
2717 and then Present (Etype (Lo))
2718 and then Scope (Etype (Lo)) /= Standard_Standard
2719 then
2720 Typ := Etype (Lo);
2722 elsif Nkind (Hi) = N_Integer_Literal
2723 and then Present (Etype (Hi))
2724 and then Scope (Etype (Hi)) /= Standard_Standard
2725 then
2726 Typ := Etype (Hi);
2728 else
2729 Typ := Standard_Integer;
2730 end if;
2731 end if;
2733 Set_Etype (R, Typ);
2735 New_Lo := One_Bound (Lo, Low_Bound (R_Copy), Typ);
2736 New_Hi := One_Bound (Hi, High_Bound (R_Copy), Typ);
2738 -- Propagate staticness to loop range itself, in case the
2739 -- corresponding subtype is static.
2741 if New_Lo /= Lo and then Is_OK_Static_Expression (New_Lo) then
2742 Rewrite (Low_Bound (R), New_Copy (New_Lo));
2743 end if;
2745 if New_Hi /= Hi and then Is_OK_Static_Expression (New_Hi) then
2746 Rewrite (High_Bound (R), New_Copy (New_Hi));
2747 end if;
2748 end Process_Bounds;
2750 -- Local variables
2752 DS : constant Node_Id := Discrete_Subtype_Definition (N);
2753 Id : constant Entity_Id := Defining_Identifier (N);
2755 DS_Copy : Node_Id;
2757 -- Start of processing for Analyze_Loop_Parameter_Specification
2759 begin
2760 Enter_Name (Id);
2762 -- We always consider the loop variable to be referenced, since the loop
2763 -- may be used just for counting purposes.
2765 Generate_Reference (Id, N, ' ');
2767 -- Check for the case of loop variable hiding a local variable (used
2768 -- later on to give a nice warning if the hidden variable is never
2769 -- assigned).
2771 declare
2772 H : constant Entity_Id := Homonym (Id);
2773 begin
2774 if Present (H)
2775 and then Ekind (H) = E_Variable
2776 and then Is_Discrete_Type (Etype (H))
2777 and then Enclosing_Dynamic_Scope (H) = Enclosing_Dynamic_Scope (Id)
2778 then
2779 Set_Hiding_Loop_Variable (H, Id);
2780 end if;
2781 end;
2783 -- Loop parameter specification must include subtype mark in SPARK
2785 if Nkind (DS) = N_Range then
2786 Check_SPARK_05_Restriction
2787 ("loop parameter specification must include subtype mark", N);
2788 end if;
2790 -- Analyze the subtype definition and create temporaries for the bounds.
2791 -- Do not evaluate the range when preanalyzing a quantified expression
2792 -- because bounds expressed as function calls with side effects will be
2793 -- incorrectly replicated.
2795 if Nkind (DS) = N_Range
2796 and then Expander_Active
2797 and then Nkind (Parent (N)) /= N_Quantified_Expression
2798 then
2799 Process_Bounds (DS);
2801 -- Either the expander not active or the range of iteration is a subtype
2802 -- indication, an entity, or a function call that yields an aggregate or
2803 -- a container.
2805 else
2806 DS_Copy := New_Copy_Tree (DS);
2807 Set_Parent (DS_Copy, Parent (DS));
2808 Preanalyze_Range (DS_Copy);
2810 -- Ada 2012: If the domain of iteration is:
2812 -- a) a function call,
2813 -- b) an identifier that is not a type,
2814 -- c) an attribute reference 'Old (within a postcondition),
2815 -- d) an unchecked conversion or a qualified expression with
2816 -- the proper iterator type.
2818 -- then it is an iteration over a container. It was classified as
2819 -- a loop specification by the parser, and must be rewritten now
2820 -- to activate container iteration. The last case will occur within
2821 -- an expanded inlined call, where the expansion wraps an actual in
2822 -- an unchecked conversion when needed. The expression of the
2823 -- conversion is always an object.
2825 if Nkind (DS_Copy) = N_Function_Call
2827 or else (Is_Entity_Name (DS_Copy)
2828 and then not Is_Type (Entity (DS_Copy)))
2830 or else (Nkind (DS_Copy) = N_Attribute_Reference
2831 and then Nam_In (Attribute_Name (DS_Copy),
2832 Name_Loop_Entry, Name_Old))
2834 or else Has_Aspect (Etype (DS_Copy), Aspect_Iterable)
2836 or else Nkind (DS_Copy) = N_Unchecked_Type_Conversion
2837 or else (Nkind (DS_Copy) = N_Qualified_Expression
2838 and then Is_Iterator (Etype (DS_Copy)))
2839 then
2840 -- This is an iterator specification. Rewrite it as such and
2841 -- analyze it to capture function calls that may require
2842 -- finalization actions.
2844 declare
2845 I_Spec : constant Node_Id :=
2846 Make_Iterator_Specification (Sloc (N),
2847 Defining_Identifier => Relocate_Node (Id),
2848 Name => DS_Copy,
2849 Subtype_Indication => Empty,
2850 Reverse_Present => Reverse_Present (N));
2851 Scheme : constant Node_Id := Parent (N);
2853 begin
2854 Set_Iterator_Specification (Scheme, I_Spec);
2855 Set_Loop_Parameter_Specification (Scheme, Empty);
2856 Analyze_Iterator_Specification (I_Spec);
2858 -- In a generic context, analyze the original domain of
2859 -- iteration, for name capture.
2861 if not Expander_Active then
2862 Analyze (DS);
2863 end if;
2865 -- Set kind of loop parameter, which may be used in the
2866 -- subsequent analysis of the condition in a quantified
2867 -- expression.
2869 Set_Ekind (Id, E_Loop_Parameter);
2870 return;
2871 end;
2873 -- Domain of iteration is not a function call, and is side-effect
2874 -- free.
2876 else
2877 -- A quantified expression that appears in a pre/post condition
2878 -- is pre-analyzed several times. If the range is given by an
2879 -- attribute reference it is rewritten as a range, and this is
2880 -- done even with expansion disabled. If the type is already set
2881 -- do not reanalyze, because a range with static bounds may be
2882 -- typed Integer by default.
2884 if Nkind (Parent (N)) = N_Quantified_Expression
2885 and then Present (Etype (DS))
2886 then
2887 null;
2888 else
2889 Analyze (DS);
2890 end if;
2891 end if;
2892 end if;
2894 if DS = Error then
2895 return;
2896 end if;
2898 -- Some additional checks if we are iterating through a type
2900 if Is_Entity_Name (DS)
2901 and then Present (Entity (DS))
2902 and then Is_Type (Entity (DS))
2903 then
2904 -- The subtype indication may denote the completion of an incomplete
2905 -- type declaration.
2907 if Ekind (Entity (DS)) = E_Incomplete_Type then
2908 Set_Entity (DS, Get_Full_View (Entity (DS)));
2909 Set_Etype (DS, Entity (DS));
2910 end if;
2912 Check_Predicate_Use (Entity (DS));
2913 end if;
2915 -- Error if not discrete type
2917 if not Is_Discrete_Type (Etype (DS)) then
2918 Wrong_Type (DS, Any_Discrete);
2919 Set_Etype (DS, Any_Type);
2920 end if;
2922 Check_Controlled_Array_Attribute (DS);
2924 if Nkind (DS) = N_Subtype_Indication then
2925 Check_Predicate_Use (Entity (Subtype_Mark (DS)));
2926 end if;
2928 Make_Index (DS, N, In_Iter_Schm => True);
2929 Set_Ekind (Id, E_Loop_Parameter);
2931 -- A quantified expression which appears in a pre- or post-condition may
2932 -- be analyzed multiple times. The analysis of the range creates several
2933 -- itypes which reside in different scopes depending on whether the pre-
2934 -- or post-condition has been expanded. Update the type of the loop
2935 -- variable to reflect the proper itype at each stage of analysis.
2937 if No (Etype (Id))
2938 or else Etype (Id) = Any_Type
2939 or else
2940 (Present (Etype (Id))
2941 and then Is_Itype (Etype (Id))
2942 and then Nkind (Parent (Loop_Nod)) = N_Expression_With_Actions
2943 and then Nkind (Original_Node (Parent (Loop_Nod))) =
2944 N_Quantified_Expression)
2945 then
2946 Set_Etype (Id, Etype (DS));
2947 end if;
2949 -- Treat a range as an implicit reference to the type, to inhibit
2950 -- spurious warnings.
2952 Generate_Reference (Base_Type (Etype (DS)), N, ' ');
2953 Set_Is_Known_Valid (Id, True);
2955 -- The loop is not a declarative part, so the loop variable must be
2956 -- frozen explicitly. Do not freeze while preanalyzing a quantified
2957 -- expression because the freeze node will not be inserted into the
2958 -- tree due to flag Is_Spec_Expression being set.
2960 if Nkind (Parent (N)) /= N_Quantified_Expression then
2961 declare
2962 Flist : constant List_Id := Freeze_Entity (Id, N);
2963 begin
2964 if Is_Non_Empty_List (Flist) then
2965 Insert_Actions (N, Flist);
2966 end if;
2967 end;
2968 end if;
2970 -- Case where we have a range or a subtype, get type bounds
2972 if Nkind_In (DS, N_Range, N_Subtype_Indication)
2973 and then not Error_Posted (DS)
2974 and then Etype (DS) /= Any_Type
2975 and then Is_Discrete_Type (Etype (DS))
2976 then
2977 declare
2978 L : Node_Id;
2979 H : Node_Id;
2981 begin
2982 if Nkind (DS) = N_Range then
2983 L := Low_Bound (DS);
2984 H := High_Bound (DS);
2985 else
2986 L :=
2987 Type_Low_Bound (Underlying_Type (Etype (Subtype_Mark (DS))));
2988 H :=
2989 Type_High_Bound (Underlying_Type (Etype (Subtype_Mark (DS))));
2990 end if;
2992 -- Check for null or possibly null range and issue warning. We
2993 -- suppress such messages in generic templates and instances,
2994 -- because in practice they tend to be dubious in these cases. The
2995 -- check applies as well to rewritten array element loops where a
2996 -- null range may be detected statically.
2998 if Compile_Time_Compare (L, H, Assume_Valid => True) = GT then
3000 -- Suppress the warning if inside a generic template or
3001 -- instance, since in practice they tend to be dubious in these
3002 -- cases since they can result from intended parameterization.
3004 if not Inside_A_Generic and then not In_Instance then
3006 -- Specialize msg if invalid values could make the loop
3007 -- non-null after all.
3009 if Compile_Time_Compare
3010 (L, H, Assume_Valid => False) = GT
3011 then
3012 -- Since we know the range of the loop is null, set the
3013 -- appropriate flag to remove the loop entirely during
3014 -- expansion.
3016 Set_Is_Null_Loop (Loop_Nod);
3018 if Comes_From_Source (N) then
3019 Error_Msg_N
3020 ("??loop range is null, loop will not execute", DS);
3021 end if;
3023 -- Here is where the loop could execute because of
3024 -- invalid values, so issue appropriate message and in
3025 -- this case we do not set the Is_Null_Loop flag since
3026 -- the loop may execute.
3028 elsif Comes_From_Source (N) then
3029 Error_Msg_N
3030 ("??loop range may be null, loop may not execute",
3031 DS);
3032 Error_Msg_N
3033 ("??can only execute if invalid values are present",
3034 DS);
3035 end if;
3036 end if;
3038 -- In either case, suppress warnings in the body of the loop,
3039 -- since it is likely that these warnings will be inappropriate
3040 -- if the loop never actually executes, which is likely.
3042 Set_Suppress_Loop_Warnings (Loop_Nod);
3044 -- The other case for a warning is a reverse loop where the
3045 -- upper bound is the integer literal zero or one, and the
3046 -- lower bound may exceed this value.
3048 -- For example, we have
3050 -- for J in reverse N .. 1 loop
3052 -- In practice, this is very likely to be a case of reversing
3053 -- the bounds incorrectly in the range.
3055 elsif Reverse_Present (N)
3056 and then Nkind (Original_Node (H)) = N_Integer_Literal
3057 and then
3058 (Intval (Original_Node (H)) = Uint_0
3059 or else
3060 Intval (Original_Node (H)) = Uint_1)
3061 then
3062 -- Lower bound may in fact be known and known not to exceed
3063 -- upper bound (e.g. reverse 0 .. 1) and that's OK.
3065 if Compile_Time_Known_Value (L)
3066 and then Expr_Value (L) <= Expr_Value (H)
3067 then
3068 null;
3070 -- Otherwise warning is warranted
3072 else
3073 Error_Msg_N ("??loop range may be null", DS);
3074 Error_Msg_N ("\??bounds may be wrong way round", DS);
3075 end if;
3076 end if;
3078 -- Check if either bound is known to be outside the range of the
3079 -- loop parameter type, this is e.g. the case of a loop from
3080 -- 20..X where the type is 1..19.
3082 -- Such a loop is dubious since either it raises CE or it executes
3083 -- zero times, and that cannot be useful!
3085 if Etype (DS) /= Any_Type
3086 and then not Error_Posted (DS)
3087 and then Nkind (DS) = N_Subtype_Indication
3088 and then Nkind (Constraint (DS)) = N_Range_Constraint
3089 then
3090 declare
3091 LLo : constant Node_Id :=
3092 Low_Bound (Range_Expression (Constraint (DS)));
3093 LHi : constant Node_Id :=
3094 High_Bound (Range_Expression (Constraint (DS)));
3096 Bad_Bound : Node_Id := Empty;
3097 -- Suspicious loop bound
3099 begin
3100 -- At this stage L, H are the bounds of the type, and LLo
3101 -- Lhi are the low bound and high bound of the loop.
3103 if Compile_Time_Compare (LLo, L, Assume_Valid => True) = LT
3104 or else
3105 Compile_Time_Compare (LLo, H, Assume_Valid => True) = GT
3106 then
3107 Bad_Bound := LLo;
3108 end if;
3110 if Compile_Time_Compare (LHi, L, Assume_Valid => True) = LT
3111 or else
3112 Compile_Time_Compare (LHi, H, Assume_Valid => True) = GT
3113 then
3114 Bad_Bound := LHi;
3115 end if;
3117 if Present (Bad_Bound) then
3118 Error_Msg_N
3119 ("suspicious loop bound out of range of "
3120 & "loop subtype??", Bad_Bound);
3121 Error_Msg_N
3122 ("\loop executes zero times or raises "
3123 & "Constraint_Error??", Bad_Bound);
3124 end if;
3125 end;
3126 end if;
3128 -- This declare block is about warnings, if we get an exception while
3129 -- testing for warnings, we simply abandon the attempt silently. This
3130 -- most likely occurs as the result of a previous error, but might
3131 -- just be an obscure case we have missed. In either case, not giving
3132 -- the warning is perfectly acceptable.
3134 exception
3135 when others => null;
3136 end;
3137 end if;
3139 -- A loop parameter cannot be effectively volatile (SPARK RM 7.1.3(4)).
3140 -- This check is relevant only when SPARK_Mode is on as it is not a
3141 -- standard Ada legality check.
3143 if SPARK_Mode = On and then Is_Effectively_Volatile (Id) then
3144 Error_Msg_N ("loop parameter cannot be volatile", Id);
3145 end if;
3146 end Analyze_Loop_Parameter_Specification;
3148 ----------------------------
3149 -- Analyze_Loop_Statement --
3150 ----------------------------
3152 procedure Analyze_Loop_Statement (N : Node_Id) is
3154 function Is_Container_Iterator (Iter : Node_Id) return Boolean;
3155 -- Given a loop iteration scheme, determine whether it is an Ada 2012
3156 -- container iteration.
3158 function Is_Wrapped_In_Block (N : Node_Id) return Boolean;
3159 -- Determine whether loop statement N has been wrapped in a block to
3160 -- capture finalization actions that may be generated for container
3161 -- iterators. Prevents infinite recursion when block is analyzed.
3162 -- Routine is a noop if loop is single statement within source block.
3164 ---------------------------
3165 -- Is_Container_Iterator --
3166 ---------------------------
3168 function Is_Container_Iterator (Iter : Node_Id) return Boolean is
3169 begin
3170 -- Infinite loop
3172 if No (Iter) then
3173 return False;
3175 -- While loop
3177 elsif Present (Condition (Iter)) then
3178 return False;
3180 -- for Def_Id in [reverse] Name loop
3181 -- for Def_Id [: Subtype_Indication] of [reverse] Name loop
3183 elsif Present (Iterator_Specification (Iter)) then
3184 declare
3185 Nam : constant Node_Id := Name (Iterator_Specification (Iter));
3186 Nam_Copy : Node_Id;
3188 begin
3189 Nam_Copy := New_Copy_Tree (Nam);
3190 Set_Parent (Nam_Copy, Parent (Nam));
3191 Preanalyze_Range (Nam_Copy);
3193 -- The only two options here are iteration over a container or
3194 -- an array.
3196 return not Is_Array_Type (Etype (Nam_Copy));
3197 end;
3199 -- for Def_Id in [reverse] Discrete_Subtype_Definition loop
3201 else
3202 declare
3203 LP : constant Node_Id := Loop_Parameter_Specification (Iter);
3204 DS : constant Node_Id := Discrete_Subtype_Definition (LP);
3205 DS_Copy : Node_Id;
3207 begin
3208 DS_Copy := New_Copy_Tree (DS);
3209 Set_Parent (DS_Copy, Parent (DS));
3210 Preanalyze_Range (DS_Copy);
3212 -- Check for a call to Iterate () or an expression with
3213 -- an iterator type.
3215 return
3216 (Nkind (DS_Copy) = N_Function_Call
3217 and then Needs_Finalization (Etype (DS_Copy)))
3218 or else Is_Iterator (Etype (DS_Copy));
3219 end;
3220 end if;
3221 end Is_Container_Iterator;
3223 -------------------------
3224 -- Is_Wrapped_In_Block --
3225 -------------------------
3227 function Is_Wrapped_In_Block (N : Node_Id) return Boolean is
3228 HSS : Node_Id;
3229 Stat : Node_Id;
3231 begin
3233 -- Check if current scope is a block that is not a transient block.
3235 if Ekind (Current_Scope) /= E_Block
3236 or else No (Block_Node (Current_Scope))
3237 then
3238 return False;
3240 else
3241 HSS :=
3242 Handled_Statement_Sequence (Parent (Block_Node (Current_Scope)));
3244 -- Skip leading pragmas that may be introduced for invariant and
3245 -- predicate checks.
3247 Stat := First (Statements (HSS));
3248 while Present (Stat) and then Nkind (Stat) = N_Pragma loop
3249 Stat := Next (Stat);
3250 end loop;
3252 return Stat = N and then No (Next (Stat));
3253 end if;
3254 end Is_Wrapped_In_Block;
3256 -- Local declarations
3258 Id : constant Node_Id := Identifier (N);
3259 Iter : constant Node_Id := Iteration_Scheme (N);
3260 Loc : constant Source_Ptr := Sloc (N);
3261 Ent : Entity_Id;
3262 Stmt : Node_Id;
3264 -- Start of processing for Analyze_Loop_Statement
3266 begin
3267 if Present (Id) then
3269 -- Make name visible, e.g. for use in exit statements. Loop labels
3270 -- are always considered to be referenced.
3272 Analyze (Id);
3273 Ent := Entity (Id);
3275 -- Guard against serious error (typically, a scope mismatch when
3276 -- semantic analysis is requested) by creating loop entity to
3277 -- continue analysis.
3279 if No (Ent) then
3280 if Total_Errors_Detected /= 0 then
3281 Ent := New_Internal_Entity (E_Loop, Current_Scope, Loc, 'L');
3282 else
3283 raise Program_Error;
3284 end if;
3286 -- Verify that the loop name is hot hidden by an unrelated
3287 -- declaration in an inner scope.
3289 elsif Ekind (Ent) /= E_Label and then Ekind (Ent) /= E_Loop then
3290 Error_Msg_Sloc := Sloc (Ent);
3291 Error_Msg_N ("implicit label declaration for & is hidden#", Id);
3293 if Present (Homonym (Ent))
3294 and then Ekind (Homonym (Ent)) = E_Label
3295 then
3296 Set_Entity (Id, Ent);
3297 Set_Ekind (Ent, E_Loop);
3298 end if;
3300 else
3301 Generate_Reference (Ent, N, ' ');
3302 Generate_Definition (Ent);
3304 -- If we found a label, mark its type. If not, ignore it, since it
3305 -- means we have a conflicting declaration, which would already
3306 -- have been diagnosed at declaration time. Set Label_Construct
3307 -- of the implicit label declaration, which is not created by the
3308 -- parser for generic units.
3310 if Ekind (Ent) = E_Label then
3311 Set_Ekind (Ent, E_Loop);
3313 if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
3314 Set_Label_Construct (Parent (Ent), N);
3315 end if;
3316 end if;
3317 end if;
3319 -- Case of no identifier present. Create one and attach it to the
3320 -- loop statement for use as a scope and as a reference for later
3321 -- expansions. Indicate that the label does not come from source,
3322 -- and attach it to the loop statement so it is part of the tree,
3323 -- even without a full declaration.
3325 else
3326 Ent := New_Internal_Entity (E_Loop, Current_Scope, Loc, 'L');
3327 Set_Etype (Ent, Standard_Void_Type);
3328 Set_Identifier (N, New_Occurrence_Of (Ent, Loc));
3329 Set_Parent (Ent, N);
3330 Set_Has_Created_Identifier (N);
3331 end if;
3333 -- If the iterator specification has a syntactic error, transform
3334 -- construct into an infinite loop to prevent a crash and perform
3335 -- some analysis.
3337 if Present (Iter)
3338 and then Present (Iterator_Specification (Iter))
3339 and then Error_Posted (Iterator_Specification (Iter))
3340 then
3341 Set_Iteration_Scheme (N, Empty);
3342 Analyze (N);
3343 return;
3344 end if;
3346 -- Iteration over a container in Ada 2012 involves the creation of a
3347 -- controlled iterator object. Wrap the loop in a block to ensure the
3348 -- timely finalization of the iterator and release of container locks.
3349 -- The same applies to the use of secondary stack when obtaining an
3350 -- iterator.
3352 if Ada_Version >= Ada_2012
3353 and then Is_Container_Iterator (Iter)
3354 and then not Is_Wrapped_In_Block (N)
3355 then
3356 declare
3357 Block_Nod : Node_Id;
3358 Block_Id : Entity_Id;
3360 begin
3361 Block_Nod :=
3362 Make_Block_Statement (Loc,
3363 Declarations => New_List,
3364 Handled_Statement_Sequence =>
3365 Make_Handled_Sequence_Of_Statements (Loc,
3366 Statements => New_List (Relocate_Node (N))));
3368 Add_Block_Identifier (Block_Nod, Block_Id);
3370 -- The expansion of iterator loops generates an iterator in order
3371 -- to traverse the elements of a container:
3373 -- Iter : <iterator type> := Iterate (Container)'reference;
3375 -- The iterator is controlled and returned on the secondary stack.
3376 -- The analysis of the call to Iterate establishes a transient
3377 -- scope to deal with the secondary stack management, but never
3378 -- really creates a physical block as this would kill the iterator
3379 -- too early (see Wrap_Transient_Declaration). To address this
3380 -- case, mark the generated block as needing secondary stack
3381 -- management.
3383 Set_Uses_Sec_Stack (Block_Id);
3385 Rewrite (N, Block_Nod);
3386 Analyze (N);
3387 return;
3388 end;
3389 end if;
3391 -- Kill current values on entry to loop, since statements in the body of
3392 -- the loop may have been executed before the loop is entered. Similarly
3393 -- we kill values after the loop, since we do not know that the body of
3394 -- the loop was executed.
3396 Kill_Current_Values;
3397 Push_Scope (Ent);
3398 Analyze_Iteration_Scheme (Iter);
3400 -- Check for following case which merits a warning if the type E of is
3401 -- a multi-dimensional array (and no explicit subscript ranges present).
3403 -- for J in E'Range
3404 -- for K in E'Range
3406 if Present (Iter)
3407 and then Present (Loop_Parameter_Specification (Iter))
3408 then
3409 declare
3410 LPS : constant Node_Id := Loop_Parameter_Specification (Iter);
3411 DSD : constant Node_Id :=
3412 Original_Node (Discrete_Subtype_Definition (LPS));
3413 begin
3414 if Nkind (DSD) = N_Attribute_Reference
3415 and then Attribute_Name (DSD) = Name_Range
3416 and then No (Expressions (DSD))
3417 then
3418 declare
3419 Typ : constant Entity_Id := Etype (Prefix (DSD));
3420 begin
3421 if Is_Array_Type (Typ)
3422 and then Number_Dimensions (Typ) > 1
3423 and then Nkind (Parent (N)) = N_Loop_Statement
3424 and then Present (Iteration_Scheme (Parent (N)))
3425 then
3426 declare
3427 OIter : constant Node_Id :=
3428 Iteration_Scheme (Parent (N));
3429 OLPS : constant Node_Id :=
3430 Loop_Parameter_Specification (OIter);
3431 ODSD : constant Node_Id :=
3432 Original_Node (Discrete_Subtype_Definition (OLPS));
3433 begin
3434 if Nkind (ODSD) = N_Attribute_Reference
3435 and then Attribute_Name (ODSD) = Name_Range
3436 and then No (Expressions (ODSD))
3437 and then Etype (Prefix (ODSD)) = Typ
3438 then
3439 Error_Msg_Sloc := Sloc (ODSD);
3440 Error_Msg_N
3441 ("inner range same as outer range#??", DSD);
3442 end if;
3443 end;
3444 end if;
3445 end;
3446 end if;
3447 end;
3448 end if;
3450 -- Analyze the statements of the body except in the case of an Ada 2012
3451 -- iterator with the expander active. In this case the expander will do
3452 -- a rewrite of the loop into a while loop. We will then analyze the
3453 -- loop body when we analyze this while loop.
3455 -- We need to do this delay because if the container is for indefinite
3456 -- types the actual subtype of the components will only be determined
3457 -- when the cursor declaration is analyzed.
3459 -- If the expander is not active then we want to analyze the loop body
3460 -- now even in the Ada 2012 iterator case, since the rewriting will not
3461 -- be done. Insert the loop variable in the current scope, if not done
3462 -- when analysing the iteration scheme. Set its kind properly to detect
3463 -- improper uses in the loop body.
3465 -- In GNATprove mode, we do one of the above depending on the kind of
3466 -- loop. If it is an iterator over an array, then we do not analyze the
3467 -- loop now. We will analyze it after it has been rewritten by the
3468 -- special SPARK expansion which is activated in GNATprove mode. We need
3469 -- to do this so that other expansions that should occur in GNATprove
3470 -- mode take into account the specificities of the rewritten loop, in
3471 -- particular the introduction of a renaming (which needs to be
3472 -- expanded).
3474 -- In other cases in GNATprove mode then we want to analyze the loop
3475 -- body now, since no rewriting will occur. Within a generic the
3476 -- GNATprove mode is irrelevant, we must analyze the generic for
3477 -- non-local name capture.
3479 if Present (Iter)
3480 and then Present (Iterator_Specification (Iter))
3481 then
3482 if GNATprove_Mode
3483 and then Is_Iterator_Over_Array (Iterator_Specification (Iter))
3484 and then not Inside_A_Generic
3485 then
3486 null;
3488 elsif not Expander_Active then
3489 declare
3490 I_Spec : constant Node_Id := Iterator_Specification (Iter);
3491 Id : constant Entity_Id := Defining_Identifier (I_Spec);
3493 begin
3494 if Scope (Id) /= Current_Scope then
3495 Enter_Name (Id);
3496 end if;
3498 -- In an element iterator, The loop parameter is a variable if
3499 -- the domain of iteration (container or array) is a variable.
3501 if not Of_Present (I_Spec)
3502 or else not Is_Variable (Name (I_Spec))
3503 then
3504 Set_Ekind (Id, E_Loop_Parameter);
3505 end if;
3506 end;
3508 Analyze_Statements (Statements (N));
3509 end if;
3511 else
3513 -- Pre-Ada2012 for-loops and while loops.
3515 Analyze_Statements (Statements (N));
3516 end if;
3518 -- When the iteration scheme of a loop contains attribute 'Loop_Entry,
3519 -- the loop is transformed into a conditional block. Retrieve the loop.
3521 Stmt := N;
3523 if Subject_To_Loop_Entry_Attributes (Stmt) then
3524 Stmt := Find_Loop_In_Conditional_Block (Stmt);
3525 end if;
3527 -- Finish up processing for the loop. We kill all current values, since
3528 -- in general we don't know if the statements in the loop have been
3529 -- executed. We could do a bit better than this with a loop that we
3530 -- know will execute at least once, but it's not worth the trouble and
3531 -- the front end is not in the business of flow tracing.
3533 Process_End_Label (Stmt, 'e', Ent);
3534 End_Scope;
3535 Kill_Current_Values;
3537 -- Check for infinite loop. Skip check for generated code, since it
3538 -- justs waste time and makes debugging the routine called harder.
3540 -- Note that we have to wait till the body of the loop is fully analyzed
3541 -- before making this call, since Check_Infinite_Loop_Warning relies on
3542 -- being able to use semantic visibility information to find references.
3544 if Comes_From_Source (Stmt) then
3545 Check_Infinite_Loop_Warning (Stmt);
3546 end if;
3548 -- Code after loop is unreachable if the loop has no WHILE or FOR and
3549 -- contains no EXIT statements within the body of the loop.
3551 if No (Iter) and then not Has_Exit (Ent) then
3552 Check_Unreachable_Code (Stmt);
3553 end if;
3554 end Analyze_Loop_Statement;
3556 ----------------------------
3557 -- Analyze_Null_Statement --
3558 ----------------------------
3560 -- Note: the semantics of the null statement is implemented by a single
3561 -- null statement, too bad everything isn't as simple as this.
3563 procedure Analyze_Null_Statement (N : Node_Id) is
3564 pragma Warnings (Off, N);
3565 begin
3566 null;
3567 end Analyze_Null_Statement;
3569 -------------------------
3570 -- Analyze_Target_Name --
3571 -------------------------
3573 procedure Analyze_Target_Name (N : Node_Id) is
3574 begin
3575 -- A target name has the type of the left-hand side of the enclosing
3576 -- assignment.
3578 Set_Etype (N, Etype (Name (Current_Assignment)));
3579 end Analyze_Target_Name;
3581 ------------------------
3582 -- Analyze_Statements --
3583 ------------------------
3585 procedure Analyze_Statements (L : List_Id) is
3586 Lab : Entity_Id;
3587 S : Node_Id;
3589 begin
3590 -- The labels declared in the statement list are reachable from
3591 -- statements in the list. We do this as a prepass so that any goto
3592 -- statement will be properly flagged if its target is not reachable.
3593 -- This is not required, but is nice behavior.
3595 S := First (L);
3596 while Present (S) loop
3597 if Nkind (S) = N_Label then
3598 Analyze (Identifier (S));
3599 Lab := Entity (Identifier (S));
3601 -- If we found a label mark it as reachable
3603 if Ekind (Lab) = E_Label then
3604 Generate_Definition (Lab);
3605 Set_Reachable (Lab);
3607 if Nkind (Parent (Lab)) = N_Implicit_Label_Declaration then
3608 Set_Label_Construct (Parent (Lab), S);
3609 end if;
3611 -- If we failed to find a label, it means the implicit declaration
3612 -- of the label was hidden. A for-loop parameter can do this to
3613 -- a label with the same name inside the loop, since the implicit
3614 -- label declaration is in the innermost enclosing body or block
3615 -- statement.
3617 else
3618 Error_Msg_Sloc := Sloc (Lab);
3619 Error_Msg_N
3620 ("implicit label declaration for & is hidden#",
3621 Identifier (S));
3622 end if;
3623 end if;
3625 Next (S);
3626 end loop;
3628 -- Perform semantic analysis on all statements
3630 Conditional_Statements_Begin;
3632 S := First (L);
3633 while Present (S) loop
3634 Analyze (S);
3636 -- Remove dimension in all statements
3638 Remove_Dimension_In_Statement (S);
3639 Next (S);
3640 end loop;
3642 Conditional_Statements_End;
3644 -- Make labels unreachable. Visibility is not sufficient, because labels
3645 -- in one if-branch for example are not reachable from the other branch,
3646 -- even though their declarations are in the enclosing declarative part.
3648 S := First (L);
3649 while Present (S) loop
3650 if Nkind (S) = N_Label then
3651 Set_Reachable (Entity (Identifier (S)), False);
3652 end if;
3654 Next (S);
3655 end loop;
3656 end Analyze_Statements;
3658 ----------------------------
3659 -- Check_Unreachable_Code --
3660 ----------------------------
3662 procedure Check_Unreachable_Code (N : Node_Id) is
3663 Error_Node : Node_Id;
3664 P : Node_Id;
3666 begin
3667 if Is_List_Member (N) and then Comes_From_Source (N) then
3668 declare
3669 Nxt : Node_Id;
3671 begin
3672 Nxt := Original_Node (Next (N));
3674 -- Skip past pragmas
3676 while Nkind (Nxt) = N_Pragma loop
3677 Nxt := Original_Node (Next (Nxt));
3678 end loop;
3680 -- If a label follows us, then we never have dead code, since
3681 -- someone could branch to the label, so we just ignore it, unless
3682 -- we are in formal mode where goto statements are not allowed.
3684 if Nkind (Nxt) = N_Label
3685 and then not Restriction_Check_Required (SPARK_05)
3686 then
3687 return;
3689 -- Otherwise see if we have a real statement following us
3691 elsif Present (Nxt)
3692 and then Comes_From_Source (Nxt)
3693 and then Is_Statement (Nxt)
3694 then
3695 -- Special very annoying exception. If we have a return that
3696 -- follows a raise, then we allow it without a warning, since
3697 -- the Ada RM annoyingly requires a useless return here.
3699 if Nkind (Original_Node (N)) /= N_Raise_Statement
3700 or else Nkind (Nxt) /= N_Simple_Return_Statement
3701 then
3702 -- The rather strange shenanigans with the warning message
3703 -- here reflects the fact that Kill_Dead_Code is very good
3704 -- at removing warnings in deleted code, and this is one
3705 -- warning we would prefer NOT to have removed.
3707 Error_Node := Nxt;
3709 -- If we have unreachable code, analyze and remove the
3710 -- unreachable code, since it is useless and we don't
3711 -- want to generate junk warnings.
3713 -- We skip this step if we are not in code generation mode
3714 -- or CodePeer mode.
3716 -- This is the one case where we remove dead code in the
3717 -- semantics as opposed to the expander, and we do not want
3718 -- to remove code if we are not in code generation mode,
3719 -- since this messes up the ASIS trees or loses useful
3720 -- information in the CodePeer tree.
3722 -- Note that one might react by moving the whole circuit to
3723 -- exp_ch5, but then we lose the warning in -gnatc mode.
3725 if Operating_Mode = Generate_Code
3726 and then not CodePeer_Mode
3727 then
3728 loop
3729 Nxt := Next (N);
3731 -- Quit deleting when we have nothing more to delete
3732 -- or if we hit a label (since someone could transfer
3733 -- control to a label, so we should not delete it).
3735 exit when No (Nxt) or else Nkind (Nxt) = N_Label;
3737 -- Statement/declaration is to be deleted
3739 Analyze (Nxt);
3740 Remove (Nxt);
3741 Kill_Dead_Code (Nxt);
3742 end loop;
3743 end if;
3745 -- Now issue the warning (or error in formal mode)
3747 if Restriction_Check_Required (SPARK_05) then
3748 Check_SPARK_05_Restriction
3749 ("unreachable code is not allowed", Error_Node);
3750 else
3751 Error_Msg
3752 ("??unreachable code!", Sloc (Error_Node), Error_Node);
3753 end if;
3754 end if;
3756 -- If the unconditional transfer of control instruction is the
3757 -- last statement of a sequence, then see if our parent is one of
3758 -- the constructs for which we count unblocked exits, and if so,
3759 -- adjust the count.
3761 else
3762 P := Parent (N);
3764 -- Statements in THEN part or ELSE part of IF statement
3766 if Nkind (P) = N_If_Statement then
3767 null;
3769 -- Statements in ELSIF part of an IF statement
3771 elsif Nkind (P) = N_Elsif_Part then
3772 P := Parent (P);
3773 pragma Assert (Nkind (P) = N_If_Statement);
3775 -- Statements in CASE statement alternative
3777 elsif Nkind (P) = N_Case_Statement_Alternative then
3778 P := Parent (P);
3779 pragma Assert (Nkind (P) = N_Case_Statement);
3781 -- Statements in body of block
3783 elsif Nkind (P) = N_Handled_Sequence_Of_Statements
3784 and then Nkind (Parent (P)) = N_Block_Statement
3785 then
3786 -- The original loop is now placed inside a block statement
3787 -- due to the expansion of attribute 'Loop_Entry. Return as
3788 -- this is not a "real" block for the purposes of exit
3789 -- counting.
3791 if Nkind (N) = N_Loop_Statement
3792 and then Subject_To_Loop_Entry_Attributes (N)
3793 then
3794 return;
3795 end if;
3797 -- Statements in exception handler in a block
3799 elsif Nkind (P) = N_Exception_Handler
3800 and then Nkind (Parent (P)) = N_Handled_Sequence_Of_Statements
3801 and then Nkind (Parent (Parent (P))) = N_Block_Statement
3802 then
3803 null;
3805 -- None of these cases, so return
3807 else
3808 return;
3809 end if;
3811 -- This was one of the cases we are looking for (i.e. the
3812 -- parent construct was IF, CASE or block) so decrement count.
3814 Unblocked_Exit_Count := Unblocked_Exit_Count - 1;
3815 end if;
3816 end;
3817 end if;
3818 end Check_Unreachable_Code;
3820 ----------------------
3821 -- Preanalyze_Range --
3822 ----------------------
3824 procedure Preanalyze_Range (R_Copy : Node_Id) is
3825 Save_Analysis : constant Boolean := Full_Analysis;
3826 Typ : Entity_Id;
3828 begin
3829 Full_Analysis := False;
3830 Expander_Mode_Save_And_Set (False);
3832 Analyze (R_Copy);
3834 if Nkind (R_Copy) in N_Subexpr and then Is_Overloaded (R_Copy) then
3836 -- Apply preference rules for range of predefined integer types, or
3837 -- check for array or iterable construct for "of" iterator, or
3838 -- diagnose true ambiguity.
3840 declare
3841 I : Interp_Index;
3842 It : Interp;
3843 Found : Entity_Id := Empty;
3845 begin
3846 Get_First_Interp (R_Copy, I, It);
3847 while Present (It.Typ) loop
3848 if Is_Discrete_Type (It.Typ) then
3849 if No (Found) then
3850 Found := It.Typ;
3851 else
3852 if Scope (Found) = Standard_Standard then
3853 null;
3855 elsif Scope (It.Typ) = Standard_Standard then
3856 Found := It.Typ;
3858 else
3859 -- Both of them are user-defined
3861 Error_Msg_N
3862 ("ambiguous bounds in range of iteration", R_Copy);
3863 Error_Msg_N ("\possible interpretations:", R_Copy);
3864 Error_Msg_NE ("\\} ", R_Copy, Found);
3865 Error_Msg_NE ("\\} ", R_Copy, It.Typ);
3866 exit;
3867 end if;
3868 end if;
3870 elsif Nkind (Parent (R_Copy)) = N_Iterator_Specification
3871 and then Of_Present (Parent (R_Copy))
3872 then
3873 if Is_Array_Type (It.Typ)
3874 or else Has_Aspect (It.Typ, Aspect_Iterator_Element)
3875 or else Has_Aspect (It.Typ, Aspect_Constant_Indexing)
3876 or else Has_Aspect (It.Typ, Aspect_Variable_Indexing)
3877 then
3878 if No (Found) then
3879 Found := It.Typ;
3880 Set_Etype (R_Copy, It.Typ);
3882 else
3883 Error_Msg_N ("ambiguous domain of iteration", R_Copy);
3884 end if;
3885 end if;
3886 end if;
3888 Get_Next_Interp (I, It);
3889 end loop;
3890 end;
3891 end if;
3893 -- Subtype mark in iteration scheme
3895 if Is_Entity_Name (R_Copy) and then Is_Type (Entity (R_Copy)) then
3896 null;
3898 -- Expression in range, or Ada 2012 iterator
3900 elsif Nkind (R_Copy) in N_Subexpr then
3901 Resolve (R_Copy);
3902 Typ := Etype (R_Copy);
3904 if Is_Discrete_Type (Typ) then
3905 null;
3907 -- Check that the resulting object is an iterable container
3909 elsif Has_Aspect (Typ, Aspect_Iterator_Element)
3910 or else Has_Aspect (Typ, Aspect_Constant_Indexing)
3911 or else Has_Aspect (Typ, Aspect_Variable_Indexing)
3912 then
3913 null;
3915 -- The expression may yield an implicit reference to an iterable
3916 -- container. Insert explicit dereference so that proper type is
3917 -- visible in the loop.
3919 elsif Has_Implicit_Dereference (Etype (R_Copy)) then
3920 declare
3921 Disc : Entity_Id;
3923 begin
3924 Disc := First_Discriminant (Typ);
3925 while Present (Disc) loop
3926 if Has_Implicit_Dereference (Disc) then
3927 Build_Explicit_Dereference (R_Copy, Disc);
3928 exit;
3929 end if;
3931 Next_Discriminant (Disc);
3932 end loop;
3933 end;
3935 end if;
3936 end if;
3938 Expander_Mode_Restore;
3939 Full_Analysis := Save_Analysis;
3940 end Preanalyze_Range;
3942 end Sem_Ch5;