Fix for ICE with -g on testcase with incomplete types.
[official-gcc.git] / gcc / ada / sem_ch5.adb
blob418ff13edbb44b7cbc3a1b50008660d69961aa8e
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-2015, 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_Ch7; use Exp_Ch7;
34 with Exp_Util; use Exp_Util;
35 with Freeze; use Freeze;
36 with Ghost; use Ghost;
37 with Lib; use Lib;
38 with Lib.Xref; use Lib.Xref;
39 with Namet; use Namet;
40 with Nlists; use Nlists;
41 with Nmake; use Nmake;
42 with Opt; use Opt;
43 with Restrict; use Restrict;
44 with Rident; use Rident;
45 with Rtsfind; use Rtsfind;
46 with Sem; use Sem;
47 with Sem_Aux; use Sem_Aux;
48 with Sem_Case; use Sem_Case;
49 with Sem_Ch3; use Sem_Ch3;
50 with Sem_Ch6; use Sem_Ch6;
51 with Sem_Ch8; use Sem_Ch8;
52 with Sem_Dim; use Sem_Dim;
53 with Sem_Disp; use Sem_Disp;
54 with Sem_Elab; use Sem_Elab;
55 with Sem_Eval; use Sem_Eval;
56 with Sem_Res; use Sem_Res;
57 with Sem_Type; use Sem_Type;
58 with Sem_Util; use Sem_Util;
59 with Sem_Warn; use Sem_Warn;
60 with Snames; use Snames;
61 with Stand; use Stand;
62 with Sinfo; use Sinfo;
63 with Targparm; use Targparm;
64 with Tbuild; use Tbuild;
65 with Uintp; use Uintp;
67 package body Sem_Ch5 is
69 Unblocked_Exit_Count : Nat := 0;
70 -- This variable is used when processing if statements, case statements,
71 -- and block statements. It counts the number of exit points that are not
72 -- blocked by unconditional transfer instructions: for IF and CASE, these
73 -- are the branches of the conditional; for a block, they are the statement
74 -- sequence of the block, and the statement sequences of any exception
75 -- handlers that are part of the block. When processing is complete, if
76 -- this count is zero, it means that control cannot fall through the IF,
77 -- CASE or block statement. This is used for the generation of warning
78 -- messages. This variable is recursively saved on entry to processing the
79 -- construct, and restored on exit.
81 procedure Preanalyze_Range (R_Copy : Node_Id);
82 -- Determine expected type of range or domain of iteration of Ada 2012
83 -- loop by analyzing separate copy. Do the analysis and resolution of the
84 -- copy of the bound(s) with expansion disabled, to prevent the generation
85 -- of finalization actions. This prevents memory leaks when the bounds
86 -- contain calls to functions returning controlled arrays or when the
87 -- domain of iteration is a container.
89 ------------------------
90 -- Analyze_Assignment --
91 ------------------------
93 procedure Analyze_Assignment (N : Node_Id) is
94 Lhs : constant Node_Id := Name (N);
95 Rhs : constant Node_Id := Expression (N);
96 T1 : Entity_Id;
97 T2 : Entity_Id;
98 Decl : Node_Id;
100 procedure Diagnose_Non_Variable_Lhs (N : Node_Id);
101 -- N is the node for the left hand side of an assignment, and it is not
102 -- a variable. This routine issues an appropriate diagnostic.
104 procedure Kill_Lhs;
105 -- This is called to kill current value settings of a simple variable
106 -- on the left hand side. We call it if we find any error in analyzing
107 -- the assignment, and at the end of processing before setting any new
108 -- current values in place.
110 procedure Set_Assignment_Type
111 (Opnd : Node_Id;
112 Opnd_Type : in out Entity_Id);
113 -- Opnd is either the Lhs or Rhs of the assignment, and Opnd_Type is the
114 -- nominal subtype. This procedure is used to deal with cases where the
115 -- nominal subtype must be replaced by the actual subtype.
117 -------------------------------
118 -- Diagnose_Non_Variable_Lhs --
119 -------------------------------
121 procedure Diagnose_Non_Variable_Lhs (N : Node_Id) is
122 begin
123 -- Not worth posting another error if left hand side already flagged
124 -- as being illegal in some respect.
126 if Error_Posted (N) then
127 return;
129 -- Some special bad cases of entity names
131 elsif Is_Entity_Name (N) then
132 declare
133 Ent : constant Entity_Id := Entity (N);
135 begin
136 if Ekind (Ent) = E_In_Parameter then
137 Error_Msg_N
138 ("assignment to IN mode parameter not allowed", N);
139 return;
141 -- Renamings of protected private components are turned into
142 -- constants when compiling a protected function. In the case
143 -- of single protected types, the private component appears
144 -- directly.
146 elsif (Is_Prival (Ent)
147 and then
148 (Ekind (Current_Scope) = E_Function
149 or else Ekind (Enclosing_Dynamic_Scope
150 (Current_Scope)) = E_Function))
151 or else
152 (Ekind (Ent) = E_Component
153 and then Is_Protected_Type (Scope (Ent)))
154 then
155 Error_Msg_N
156 ("protected function cannot modify protected object", N);
157 return;
159 elsif Ekind (Ent) = E_Loop_Parameter then
160 Error_Msg_N ("assignment to loop parameter not allowed", N);
161 return;
162 end if;
163 end;
165 -- For indexed components, test prefix if it is in array. We do not
166 -- want to recurse for cases where the prefix is a pointer, since we
167 -- may get a message confusing the pointer and what it references.
169 elsif Nkind (N) = N_Indexed_Component
170 and then Is_Array_Type (Etype (Prefix (N)))
171 then
172 Diagnose_Non_Variable_Lhs (Prefix (N));
173 return;
175 -- Another special case for assignment to discriminant
177 elsif Nkind (N) = N_Selected_Component then
178 if Present (Entity (Selector_Name (N)))
179 and then Ekind (Entity (Selector_Name (N))) = E_Discriminant
180 then
181 Error_Msg_N ("assignment to discriminant not allowed", N);
182 return;
184 -- For selection from record, diagnose prefix, but note that again
185 -- we only do this for a record, not e.g. for a pointer.
187 elsif Is_Record_Type (Etype (Prefix (N))) then
188 Diagnose_Non_Variable_Lhs (Prefix (N));
189 return;
190 end if;
191 end if;
193 -- If we fall through, we have no special message to issue
195 Error_Msg_N ("left hand side of assignment must be a variable", N);
196 end Diagnose_Non_Variable_Lhs;
198 --------------
199 -- Kill_Lhs --
200 --------------
202 procedure Kill_Lhs is
203 begin
204 if Is_Entity_Name (Lhs) then
205 declare
206 Ent : constant Entity_Id := Entity (Lhs);
207 begin
208 if Present (Ent) then
209 Kill_Current_Values (Ent);
210 end if;
211 end;
212 end if;
213 end Kill_Lhs;
215 -------------------------
216 -- Set_Assignment_Type --
217 -------------------------
219 procedure Set_Assignment_Type
220 (Opnd : Node_Id;
221 Opnd_Type : in out Entity_Id)
223 begin
224 Require_Entity (Opnd);
226 -- If the assignment operand is an in-out or out parameter, then we
227 -- get the actual subtype (needed for the unconstrained case). If the
228 -- operand is the actual in an entry declaration, then within the
229 -- accept statement it is replaced with a local renaming, which may
230 -- also have an actual subtype.
232 if Is_Entity_Name (Opnd)
233 and then (Ekind (Entity (Opnd)) = E_Out_Parameter
234 or else Ekind_In (Entity (Opnd),
235 E_In_Out_Parameter,
236 E_Generic_In_Out_Parameter)
237 or else
238 (Ekind (Entity (Opnd)) = E_Variable
239 and then Nkind (Parent (Entity (Opnd))) =
240 N_Object_Renaming_Declaration
241 and then Nkind (Parent (Parent (Entity (Opnd)))) =
242 N_Accept_Statement))
243 then
244 Opnd_Type := Get_Actual_Subtype (Opnd);
246 -- If assignment operand is a component reference, then we get the
247 -- actual subtype of the component for the unconstrained case.
249 elsif Nkind_In (Opnd, N_Selected_Component, N_Explicit_Dereference)
250 and then not Is_Unchecked_Union (Opnd_Type)
251 then
252 Decl := Build_Actual_Subtype_Of_Component (Opnd_Type, Opnd);
254 if Present (Decl) then
255 Insert_Action (N, Decl);
256 Mark_Rewrite_Insertion (Decl);
257 Analyze (Decl);
258 Opnd_Type := Defining_Identifier (Decl);
259 Set_Etype (Opnd, Opnd_Type);
260 Freeze_Itype (Opnd_Type, N);
262 elsif Is_Constrained (Etype (Opnd)) then
263 Opnd_Type := Etype (Opnd);
264 end if;
266 -- For slice, use the constrained subtype created for the slice
268 elsif Nkind (Opnd) = N_Slice then
269 Opnd_Type := Etype (Opnd);
270 end if;
271 end Set_Assignment_Type;
273 -- Local variables
275 Save_Ghost_Mode : constant Ghost_Mode_Type := Ghost_Mode;
277 -- Start of processing for Analyze_Assignment
279 begin
280 Mark_Coextensions (N, Rhs);
282 -- Analyze the target of the assignment first in case the expression
283 -- contains references to Ghost entities. The checks that verify the
284 -- proper use of a Ghost entity need to know the enclosing context.
286 Analyze (Lhs);
288 -- An assignment statement is Ghost when the left hand side denotes a
289 -- Ghost entity. Set the mode now to ensure that any nodes generated
290 -- during analysis and expansion are properly marked as Ghost.
292 Set_Ghost_Mode (N);
293 Analyze (Rhs);
295 -- Ensure that we never do an assignment on a variable marked as
296 -- as Safe_To_Reevaluate.
298 pragma Assert (not Is_Entity_Name (Lhs)
299 or else Ekind (Entity (Lhs)) /= E_Variable
300 or else not Is_Safe_To_Reevaluate (Entity (Lhs)));
302 -- Start type analysis for assignment
304 T1 := Etype (Lhs);
306 -- In the most general case, both Lhs and Rhs can be overloaded, and we
307 -- must compute the intersection of the possible types on each side.
309 if Is_Overloaded (Lhs) then
310 declare
311 I : Interp_Index;
312 It : Interp;
314 begin
315 T1 := Any_Type;
316 Get_First_Interp (Lhs, I, It);
318 while Present (It.Typ) loop
320 -- An indexed component with generalized indexing is always
321 -- overloaded with the corresponding dereference. Discard the
322 -- interpretation that yields a reference type, which is not
323 -- assignable.
325 if Nkind (Lhs) = N_Indexed_Component
326 and then Present (Generalized_Indexing (Lhs))
327 and then Has_Implicit_Dereference (It.Typ)
328 then
329 null;
331 elsif Has_Compatible_Type (Rhs, It.Typ) then
332 if T1 /= Any_Type then
334 -- An explicit dereference is overloaded if the prefix
335 -- is. Try to remove the ambiguity on the prefix, the
336 -- error will be posted there if the ambiguity is real.
338 if Nkind (Lhs) = N_Explicit_Dereference then
339 declare
340 PI : Interp_Index;
341 PI1 : Interp_Index := 0;
342 PIt : Interp;
343 Found : Boolean;
345 begin
346 Found := False;
347 Get_First_Interp (Prefix (Lhs), PI, PIt);
349 while Present (PIt.Typ) loop
350 if Is_Access_Type (PIt.Typ)
351 and then Has_Compatible_Type
352 (Rhs, Designated_Type (PIt.Typ))
353 then
354 if Found then
355 PIt :=
356 Disambiguate (Prefix (Lhs),
357 PI1, PI, Any_Type);
359 if PIt = No_Interp then
360 Error_Msg_N
361 ("ambiguous left-hand side"
362 & " in assignment", Lhs);
363 exit;
364 else
365 Resolve (Prefix (Lhs), PIt.Typ);
366 end if;
368 exit;
369 else
370 Found := True;
371 PI1 := PI;
372 end if;
373 end if;
375 Get_Next_Interp (PI, PIt);
376 end loop;
377 end;
379 else
380 Error_Msg_N
381 ("ambiguous left-hand side in assignment", Lhs);
382 exit;
383 end if;
384 else
385 T1 := It.Typ;
386 end if;
387 end if;
389 Get_Next_Interp (I, It);
390 end loop;
391 end;
393 if T1 = Any_Type then
394 Error_Msg_N
395 ("no valid types for left-hand side for assignment", Lhs);
396 Kill_Lhs;
397 Ghost_Mode := Save_Ghost_Mode;
398 return;
399 end if;
400 end if;
402 -- The resulting assignment type is T1, so now we will resolve the left
403 -- hand side of the assignment using this determined type.
405 Resolve (Lhs, T1);
407 -- Cases where Lhs is not a variable
409 -- Cases where Lhs is not a variable. In an instance or an inlined body
410 -- no need for further check because assignment was legal in template.
412 if In_Inlined_Body then
413 null;
415 elsif not Is_Variable (Lhs) then
417 -- Ada 2005 (AI-327): Check assignment to the attribute Priority of a
418 -- protected object.
420 declare
421 Ent : Entity_Id;
422 S : Entity_Id;
424 begin
425 if Ada_Version >= Ada_2005 then
427 -- Handle chains of renamings
429 Ent := Lhs;
430 while Nkind (Ent) in N_Has_Entity
431 and then Present (Entity (Ent))
432 and then Present (Renamed_Object (Entity (Ent)))
433 loop
434 Ent := Renamed_Object (Entity (Ent));
435 end loop;
437 if (Nkind (Ent) = N_Attribute_Reference
438 and then Attribute_Name (Ent) = Name_Priority)
440 -- Renamings of the attribute Priority applied to protected
441 -- objects have been previously expanded into calls to the
442 -- Get_Ceiling run-time subprogram.
444 or else
445 (Nkind (Ent) = N_Function_Call
446 and then (Entity (Name (Ent)) = RTE (RE_Get_Ceiling)
447 or else
448 Entity (Name (Ent)) = RTE (RO_PE_Get_Ceiling)))
449 then
450 -- The enclosing subprogram cannot be a protected function
452 S := Current_Scope;
453 while not (Is_Subprogram (S)
454 and then Convention (S) = Convention_Protected)
455 and then S /= Standard_Standard
456 loop
457 S := Scope (S);
458 end loop;
460 if Ekind (S) = E_Function
461 and then Convention (S) = Convention_Protected
462 then
463 Error_Msg_N
464 ("protected function cannot modify protected object",
465 Lhs);
466 end if;
468 -- Changes of the ceiling priority of the protected object
469 -- are only effective if the Ceiling_Locking policy is in
470 -- effect (AARM D.5.2 (5/2)).
472 if Locking_Policy /= 'C' then
473 Error_Msg_N ("assignment to the attribute PRIORITY has " &
474 "no effect??", Lhs);
475 Error_Msg_N ("\since no Locking_Policy has been " &
476 "specified??", Lhs);
477 end if;
479 Ghost_Mode := Save_Ghost_Mode;
480 return;
481 end if;
482 end if;
483 end;
485 Diagnose_Non_Variable_Lhs (Lhs);
486 Ghost_Mode := Save_Ghost_Mode;
487 return;
489 -- Error of assigning to limited type. We do however allow this in
490 -- certain cases where the front end generates the assignments.
492 elsif Is_Limited_Type (T1)
493 and then not Assignment_OK (Lhs)
494 and then not Assignment_OK (Original_Node (Lhs))
495 then
496 -- CPP constructors can only be called in declarations
498 if Is_CPP_Constructor_Call (Rhs) then
499 Error_Msg_N ("invalid use of 'C'P'P constructor", Rhs);
500 else
501 Error_Msg_N
502 ("left hand of assignment must not be limited type", Lhs);
503 Explain_Limited_Type (T1, Lhs);
504 end if;
506 Ghost_Mode := Save_Ghost_Mode;
507 return;
509 -- Enforce RM 3.9.3 (8): the target of an assignment operation cannot be
510 -- abstract. This is only checked when the assignment Comes_From_Source,
511 -- because in some cases the expander generates such assignments (such
512 -- in the _assign operation for an abstract type).
514 elsif Is_Abstract_Type (T1) and then Comes_From_Source (N) then
515 Error_Msg_N
516 ("target of assignment operation must not be abstract", Lhs);
517 end if;
519 -- Resolution may have updated the subtype, in case the left-hand side
520 -- is a private protected component. Use the correct subtype to avoid
521 -- scoping issues in the back-end.
523 T1 := Etype (Lhs);
525 -- Ada 2005 (AI-50217, AI-326): Check wrong dereference of incomplete
526 -- type. For example:
528 -- limited with P;
529 -- package Pkg is
530 -- type Acc is access P.T;
531 -- end Pkg;
533 -- with Pkg; use Acc;
534 -- procedure Example is
535 -- A, B : Acc;
536 -- begin
537 -- A.all := B.all; -- ERROR
538 -- end Example;
540 if Nkind (Lhs) = N_Explicit_Dereference
541 and then Ekind (T1) = E_Incomplete_Type
542 then
543 Error_Msg_N ("invalid use of incomplete type", Lhs);
544 Kill_Lhs;
545 Ghost_Mode := Save_Ghost_Mode;
546 return;
547 end if;
549 -- Now we can complete the resolution of the right hand side
551 Set_Assignment_Type (Lhs, T1);
552 Resolve (Rhs, T1);
554 -- This is the point at which we check for an unset reference
556 Check_Unset_Reference (Rhs);
557 Check_Unprotected_Access (Lhs, Rhs);
559 -- Remaining steps are skipped if Rhs was syntactically in error
561 if Rhs = Error then
562 Kill_Lhs;
563 Ghost_Mode := Save_Ghost_Mode;
564 return;
565 end if;
567 T2 := Etype (Rhs);
569 if not Covers (T1, T2) then
570 Wrong_Type (Rhs, Etype (Lhs));
571 Kill_Lhs;
572 Ghost_Mode := Save_Ghost_Mode;
573 return;
574 end if;
576 -- Ada 2005 (AI-326): In case of explicit dereference of incomplete
577 -- types, use the non-limited view if available
579 if Nkind (Rhs) = N_Explicit_Dereference
580 and then Is_Tagged_Type (T2)
581 and then Has_Non_Limited_View (T2)
582 then
583 T2 := Non_Limited_View (T2);
584 end if;
586 Set_Assignment_Type (Rhs, T2);
588 if Total_Errors_Detected /= 0 then
589 if No (T1) then
590 T1 := Any_Type;
591 end if;
593 if No (T2) then
594 T2 := Any_Type;
595 end if;
596 end if;
598 if T1 = Any_Type or else T2 = Any_Type then
599 Kill_Lhs;
600 Ghost_Mode := Save_Ghost_Mode;
601 return;
602 end if;
604 -- If the rhs is class-wide or dynamically tagged, then require the lhs
605 -- to be class-wide. The case where the rhs is a dynamically tagged call
606 -- to a dispatching operation with a controlling access result is
607 -- excluded from this check, since the target has an access type (and
608 -- no tag propagation occurs in that case).
610 if (Is_Class_Wide_Type (T2)
611 or else (Is_Dynamically_Tagged (Rhs)
612 and then not Is_Access_Type (T1)))
613 and then not Is_Class_Wide_Type (T1)
614 then
615 Error_Msg_N ("dynamically tagged expression not allowed!", Rhs);
617 elsif Is_Class_Wide_Type (T1)
618 and then not Is_Class_Wide_Type (T2)
619 and then not Is_Tag_Indeterminate (Rhs)
620 and then not Is_Dynamically_Tagged (Rhs)
621 then
622 Error_Msg_N ("dynamically tagged expression required!", Rhs);
623 end if;
625 -- Propagate the tag from a class-wide target to the rhs when the rhs
626 -- is a tag-indeterminate call.
628 if Is_Tag_Indeterminate (Rhs) then
629 if Is_Class_Wide_Type (T1) then
630 Propagate_Tag (Lhs, Rhs);
632 elsif Nkind (Rhs) = N_Function_Call
633 and then Is_Entity_Name (Name (Rhs))
634 and then Is_Abstract_Subprogram (Entity (Name (Rhs)))
635 then
636 Error_Msg_N
637 ("call to abstract function must be dispatching", Name (Rhs));
639 elsif Nkind (Rhs) = N_Qualified_Expression
640 and then Nkind (Expression (Rhs)) = N_Function_Call
641 and then Is_Entity_Name (Name (Expression (Rhs)))
642 and then
643 Is_Abstract_Subprogram (Entity (Name (Expression (Rhs))))
644 then
645 Error_Msg_N
646 ("call to abstract function must be dispatching",
647 Name (Expression (Rhs)));
648 end if;
649 end if;
651 -- Ada 2005 (AI-385): When the lhs type is an anonymous access type,
652 -- apply an implicit conversion of the rhs to that type to force
653 -- appropriate static and run-time accessibility checks. This applies
654 -- as well to anonymous access-to-subprogram types that are component
655 -- subtypes or formal parameters.
657 if Ada_Version >= Ada_2005 and then Is_Access_Type (T1) then
658 if Is_Local_Anonymous_Access (T1)
659 or else Ekind (T2) = E_Anonymous_Access_Subprogram_Type
661 -- Handle assignment to an Ada 2012 stand-alone object
662 -- of an anonymous access type.
664 or else (Ekind (T1) = E_Anonymous_Access_Type
665 and then Nkind (Associated_Node_For_Itype (T1)) =
666 N_Object_Declaration)
668 then
669 Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
670 Analyze_And_Resolve (Rhs, T1);
671 end if;
672 end if;
674 -- Ada 2005 (AI-231): Assignment to not null variable
676 if Ada_Version >= Ada_2005
677 and then Can_Never_Be_Null (T1)
678 and then not Assignment_OK (Lhs)
679 then
680 -- Case where we know the right hand side is null
682 if Known_Null (Rhs) then
683 Apply_Compile_Time_Constraint_Error
684 (N => Rhs,
685 Msg =>
686 "(Ada 2005) null not allowed in null-excluding objects??",
687 Reason => CE_Null_Not_Allowed);
689 -- We still mark this as a possible modification, that's necessary
690 -- to reset Is_True_Constant, and desirable for xref purposes.
692 Note_Possible_Modification (Lhs, Sure => True);
693 Ghost_Mode := Save_Ghost_Mode;
694 return;
696 -- If we know the right hand side is non-null, then we convert to the
697 -- target type, since we don't need a run time check in that case.
699 elsif not Can_Never_Be_Null (T2) then
700 Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
701 Analyze_And_Resolve (Rhs, T1);
702 end if;
703 end if;
705 if Is_Scalar_Type (T1) then
706 Apply_Scalar_Range_Check (Rhs, Etype (Lhs));
708 -- For array types, verify that lengths match. If the right hand side
709 -- is a function call that has been inlined, the assignment has been
710 -- rewritten as a block, and the constraint check will be applied to the
711 -- assignment within the block.
713 elsif Is_Array_Type (T1)
714 and then (Nkind (Rhs) /= N_Type_Conversion
715 or else Is_Constrained (Etype (Rhs)))
716 and then (Nkind (Rhs) /= N_Function_Call
717 or else Nkind (N) /= N_Block_Statement)
718 then
719 -- Assignment verifies that the length of the Lsh and Rhs are equal,
720 -- but of course the indexes do not have to match. If the right-hand
721 -- side is a type conversion to an unconstrained type, a length check
722 -- is performed on the expression itself during expansion. In rare
723 -- cases, the redundant length check is computed on an index type
724 -- with a different representation, triggering incorrect code in the
725 -- back end.
727 Apply_Length_Check (Rhs, Etype (Lhs));
729 else
730 -- Discriminant checks are applied in the course of expansion
732 null;
733 end if;
735 -- Note: modifications of the Lhs may only be recorded after
736 -- checks have been applied.
738 Note_Possible_Modification (Lhs, Sure => True);
740 -- ??? a real accessibility check is needed when ???
742 -- Post warning for redundant assignment or variable to itself
744 if Warn_On_Redundant_Constructs
746 -- We only warn for source constructs
748 and then Comes_From_Source (N)
750 -- Where the object is the same on both sides
752 and then Same_Object (Lhs, Original_Node (Rhs))
754 -- But exclude the case where the right side was an operation that
755 -- got rewritten (e.g. JUNK + K, where K was known to be zero). We
756 -- don't want to warn in such a case, since it is reasonable to write
757 -- such expressions especially when K is defined symbolically in some
758 -- other package.
760 and then Nkind (Original_Node (Rhs)) not in N_Op
761 then
762 if Nkind (Lhs) in N_Has_Entity then
763 Error_Msg_NE -- CODEFIX
764 ("?r?useless assignment of & to itself!", N, Entity (Lhs));
765 else
766 Error_Msg_N -- CODEFIX
767 ("?r?useless assignment of object to itself!", N);
768 end if;
769 end if;
771 -- Check for non-allowed composite assignment
773 if not Support_Composite_Assign_On_Target
774 and then (Is_Array_Type (T1) or else Is_Record_Type (T1))
775 and then (not Has_Size_Clause (T1) or else Esize (T1) > 64)
776 then
777 Error_Msg_CRT ("composite assignment", N);
778 end if;
780 -- Check elaboration warning for left side if not in elab code
782 if not In_Subprogram_Or_Concurrent_Unit then
783 Check_Elab_Assign (Lhs);
784 end if;
786 -- Set Referenced_As_LHS if appropriate. We only set this flag if the
787 -- assignment is a source assignment in the extended main source unit.
788 -- We are not interested in any reference information outside this
789 -- context, or in compiler generated assignment statements.
791 if Comes_From_Source (N)
792 and then In_Extended_Main_Source_Unit (Lhs)
793 then
794 Set_Referenced_Modified (Lhs, Out_Param => False);
795 end if;
797 -- RM 7.3.2 (12/3) An assignment to a view conversion (from a type
798 -- to one of its ancestors) requires an invariant check. Apply check
799 -- only if expression comes from source, otherwise it will be applied
800 -- when value is assigned to source entity.
802 if Nkind (Lhs) = N_Type_Conversion
803 and then Has_Invariants (Etype (Expression (Lhs)))
804 and then Comes_From_Source (Expression (Lhs))
805 then
806 Insert_After (N, Make_Invariant_Call (Expression (Lhs)));
807 end if;
809 -- Final step. If left side is an entity, then we may be able to reset
810 -- the current tracked values to new safe values. We only have something
811 -- to do if the left side is an entity name, and expansion has not
812 -- modified the node into something other than an assignment, and of
813 -- course we only capture values if it is safe to do so.
815 if Is_Entity_Name (Lhs)
816 and then Nkind (N) = N_Assignment_Statement
817 then
818 declare
819 Ent : constant Entity_Id := Entity (Lhs);
821 begin
822 if Safe_To_Capture_Value (N, Ent) then
824 -- If simple variable on left side, warn if this assignment
825 -- blots out another one (rendering it useless). We only do
826 -- this for source assignments, otherwise we can generate bogus
827 -- warnings when an assignment is rewritten as another
828 -- assignment, and gets tied up with itself.
830 if Warn_On_Modified_Unread
831 and then Is_Assignable (Ent)
832 and then Comes_From_Source (N)
833 and then In_Extended_Main_Source_Unit (Ent)
834 then
835 Warn_On_Useless_Assignment (Ent, N);
836 end if;
838 -- If we are assigning an access type and the left side is an
839 -- entity, then make sure that the Is_Known_[Non_]Null flags
840 -- properly reflect the state of the entity after assignment.
842 if Is_Access_Type (T1) then
843 if Known_Non_Null (Rhs) then
844 Set_Is_Known_Non_Null (Ent, True);
846 elsif Known_Null (Rhs)
847 and then not Can_Never_Be_Null (Ent)
848 then
849 Set_Is_Known_Null (Ent, True);
851 else
852 Set_Is_Known_Null (Ent, False);
854 if not Can_Never_Be_Null (Ent) then
855 Set_Is_Known_Non_Null (Ent, False);
856 end if;
857 end if;
859 -- For discrete types, we may be able to set the current value
860 -- if the value is known at compile time.
862 elsif Is_Discrete_Type (T1)
863 and then Compile_Time_Known_Value (Rhs)
864 then
865 Set_Current_Value (Ent, Rhs);
866 else
867 Set_Current_Value (Ent, Empty);
868 end if;
870 -- If not safe to capture values, kill them
872 else
873 Kill_Lhs;
874 end if;
875 end;
876 end if;
878 -- If assigning to an object in whole or in part, note location of
879 -- assignment in case no one references value. We only do this for
880 -- source assignments, otherwise we can generate bogus warnings when an
881 -- assignment is rewritten as another assignment, and gets tied up with
882 -- itself.
884 declare
885 Ent : constant Entity_Id := Get_Enclosing_Object (Lhs);
886 begin
887 if Present (Ent)
888 and then Safe_To_Capture_Value (N, Ent)
889 and then Nkind (N) = N_Assignment_Statement
890 and then Warn_On_Modified_Unread
891 and then Is_Assignable (Ent)
892 and then Comes_From_Source (N)
893 and then In_Extended_Main_Source_Unit (Ent)
894 then
895 Set_Last_Assignment (Ent, Lhs);
896 end if;
897 end;
899 Analyze_Dimension (N);
900 Ghost_Mode := Save_Ghost_Mode;
901 end Analyze_Assignment;
903 -----------------------------
904 -- Analyze_Block_Statement --
905 -----------------------------
907 procedure Analyze_Block_Statement (N : Node_Id) is
908 procedure Install_Return_Entities (Scop : Entity_Id);
909 -- Install all entities of return statement scope Scop in the visibility
910 -- chain except for the return object since its entity is reused in a
911 -- renaming.
913 -----------------------------
914 -- Install_Return_Entities --
915 -----------------------------
917 procedure Install_Return_Entities (Scop : Entity_Id) is
918 Id : Entity_Id;
920 begin
921 Id := First_Entity (Scop);
922 while Present (Id) loop
924 -- Do not install the return object
926 if not Ekind_In (Id, E_Constant, E_Variable)
927 or else not Is_Return_Object (Id)
928 then
929 Install_Entity (Id);
930 end if;
932 Next_Entity (Id);
933 end loop;
934 end Install_Return_Entities;
936 -- Local constants and variables
938 Decls : constant List_Id := Declarations (N);
939 Id : constant Node_Id := Identifier (N);
940 HSS : constant Node_Id := Handled_Statement_Sequence (N);
942 Is_BIP_Return_Statement : Boolean;
944 -- Start of processing for Analyze_Block_Statement
946 begin
947 -- In SPARK mode, we reject block statements. Note that the case of
948 -- block statements generated by the expander is fine.
950 if Nkind (Original_Node (N)) = N_Block_Statement then
951 Check_SPARK_05_Restriction ("block statement is not allowed", N);
952 end if;
954 -- If no handled statement sequence is present, things are really messed
955 -- up, and we just return immediately (defence against previous errors).
957 if No (HSS) then
958 Check_Error_Detected;
959 return;
960 end if;
962 -- Detect whether the block is actually a rewritten return statement of
963 -- a build-in-place function.
965 Is_BIP_Return_Statement :=
966 Present (Id)
967 and then Present (Entity (Id))
968 and then Ekind (Entity (Id)) = E_Return_Statement
969 and then Is_Build_In_Place_Function
970 (Return_Applies_To (Entity (Id)));
972 -- Normal processing with HSS present
974 declare
975 EH : constant List_Id := Exception_Handlers (HSS);
976 Ent : Entity_Id := Empty;
977 S : Entity_Id;
979 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
980 -- Recursively save value of this global, will be restored on exit
982 begin
983 -- Initialize unblocked exit count for statements of begin block
984 -- plus one for each exception handler that is present.
986 Unblocked_Exit_Count := 1;
988 if Present (EH) then
989 Unblocked_Exit_Count := Unblocked_Exit_Count + List_Length (EH);
990 end if;
992 -- If a label is present analyze it and mark it as referenced
994 if Present (Id) then
995 Analyze (Id);
996 Ent := Entity (Id);
998 -- An error defense. If we have an identifier, but no entity, then
999 -- something is wrong. If previous errors, then just remove the
1000 -- identifier and continue, otherwise raise an exception.
1002 if No (Ent) then
1003 Check_Error_Detected;
1004 Set_Identifier (N, Empty);
1006 else
1007 Set_Ekind (Ent, E_Block);
1008 Generate_Reference (Ent, N, ' ');
1009 Generate_Definition (Ent);
1011 if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
1012 Set_Label_Construct (Parent (Ent), N);
1013 end if;
1014 end if;
1015 end if;
1017 -- If no entity set, create a label entity
1019 if No (Ent) then
1020 Ent := New_Internal_Entity (E_Block, Current_Scope, Sloc (N), 'B');
1021 Set_Identifier (N, New_Occurrence_Of (Ent, Sloc (N)));
1022 Set_Parent (Ent, N);
1023 end if;
1025 Set_Etype (Ent, Standard_Void_Type);
1026 Set_Block_Node (Ent, Identifier (N));
1027 Push_Scope (Ent);
1029 -- The block served as an extended return statement. Ensure that any
1030 -- entities created during the analysis and expansion of the return
1031 -- object declaration are once again visible.
1033 if Is_BIP_Return_Statement then
1034 Install_Return_Entities (Ent);
1035 end if;
1037 if Present (Decls) then
1038 Analyze_Declarations (Decls);
1039 Check_Completion;
1040 Inspect_Deferred_Constant_Completion (Decls);
1041 end if;
1043 Analyze (HSS);
1044 Process_End_Label (HSS, 'e', Ent);
1046 -- If exception handlers are present, then we indicate that enclosing
1047 -- scopes contain a block with handlers. We only need to mark non-
1048 -- generic scopes.
1050 if Present (EH) then
1051 S := Scope (Ent);
1052 loop
1053 Set_Has_Nested_Block_With_Handler (S);
1054 exit when Is_Overloadable (S)
1055 or else Ekind (S) = E_Package
1056 or else Is_Generic_Unit (S);
1057 S := Scope (S);
1058 end loop;
1059 end if;
1061 Check_References (Ent);
1062 Warn_On_Useless_Assignments (Ent);
1063 End_Scope;
1065 if Unblocked_Exit_Count = 0 then
1066 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1067 Check_Unreachable_Code (N);
1068 else
1069 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1070 end if;
1071 end;
1072 end Analyze_Block_Statement;
1074 --------------------------------
1075 -- Analyze_Compound_Statement --
1076 --------------------------------
1078 procedure Analyze_Compound_Statement (N : Node_Id) is
1079 begin
1080 Analyze_List (Actions (N));
1081 end Analyze_Compound_Statement;
1083 ----------------------------
1084 -- Analyze_Case_Statement --
1085 ----------------------------
1087 procedure Analyze_Case_Statement (N : Node_Id) is
1088 Exp : Node_Id;
1089 Exp_Type : Entity_Id;
1090 Exp_Btype : Entity_Id;
1091 Last_Choice : Nat;
1093 Others_Present : Boolean;
1094 -- Indicates if Others was present
1096 pragma Warnings (Off, Last_Choice);
1097 -- Don't care about assigned value
1099 Statements_Analyzed : Boolean := False;
1100 -- Set True if at least some statement sequences get analyzed. If False
1101 -- on exit, means we had a serious error that prevented full analysis of
1102 -- the case statement, and as a result it is not a good idea to output
1103 -- warning messages about unreachable code.
1105 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1106 -- Recursively save value of this global, will be restored on exit
1108 procedure Non_Static_Choice_Error (Choice : Node_Id);
1109 -- Error routine invoked by the generic instantiation below when the
1110 -- case statement has a non static choice.
1112 procedure Process_Statements (Alternative : Node_Id);
1113 -- Analyzes the statements associated with a case alternative. Needed
1114 -- by instantiation below.
1116 package Analyze_Case_Choices is new
1117 Generic_Analyze_Choices
1118 (Process_Associated_Node => Process_Statements);
1119 use Analyze_Case_Choices;
1120 -- Instantiation of the generic choice analysis package
1122 package Check_Case_Choices is new
1123 Generic_Check_Choices
1124 (Process_Empty_Choice => No_OP,
1125 Process_Non_Static_Choice => Non_Static_Choice_Error,
1126 Process_Associated_Node => No_OP);
1127 use Check_Case_Choices;
1128 -- Instantiation of the generic choice processing package
1130 -----------------------------
1131 -- Non_Static_Choice_Error --
1132 -----------------------------
1134 procedure Non_Static_Choice_Error (Choice : Node_Id) is
1135 begin
1136 Flag_Non_Static_Expr
1137 ("choice given in case statement is not static!", Choice);
1138 end Non_Static_Choice_Error;
1140 ------------------------
1141 -- Process_Statements --
1142 ------------------------
1144 procedure Process_Statements (Alternative : Node_Id) is
1145 Choices : constant List_Id := Discrete_Choices (Alternative);
1146 Ent : Entity_Id;
1148 begin
1149 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1150 Statements_Analyzed := True;
1152 -- An interesting optimization. If the case statement expression
1153 -- is a simple entity, then we can set the current value within an
1154 -- alternative if the alternative has one possible value.
1156 -- case N is
1157 -- when 1 => alpha
1158 -- when 2 | 3 => beta
1159 -- when others => gamma
1161 -- Here we know that N is initially 1 within alpha, but for beta and
1162 -- gamma, we do not know anything more about the initial value.
1164 if Is_Entity_Name (Exp) then
1165 Ent := Entity (Exp);
1167 if Ekind_In (Ent, E_Variable,
1168 E_In_Out_Parameter,
1169 E_Out_Parameter)
1170 then
1171 if List_Length (Choices) = 1
1172 and then Nkind (First (Choices)) in N_Subexpr
1173 and then Compile_Time_Known_Value (First (Choices))
1174 then
1175 Set_Current_Value (Entity (Exp), First (Choices));
1176 end if;
1178 Analyze_Statements (Statements (Alternative));
1180 -- After analyzing the case, set the current value to empty
1181 -- since we won't know what it is for the next alternative
1182 -- (unless reset by this same circuit), or after the case.
1184 Set_Current_Value (Entity (Exp), Empty);
1185 return;
1186 end if;
1187 end if;
1189 -- Case where expression is not an entity name of a variable
1191 Analyze_Statements (Statements (Alternative));
1192 end Process_Statements;
1194 -- Start of processing for Analyze_Case_Statement
1196 begin
1197 Unblocked_Exit_Count := 0;
1198 Exp := Expression (N);
1199 Analyze (Exp);
1201 -- The expression must be of any discrete type. In rare cases, the
1202 -- expander constructs a case statement whose expression has a private
1203 -- type whose full view is discrete. This can happen when generating
1204 -- a stream operation for a variant type after the type is frozen,
1205 -- when the partial of view of the type of the discriminant is private.
1206 -- In that case, use the full view to analyze case alternatives.
1208 if not Is_Overloaded (Exp)
1209 and then not Comes_From_Source (N)
1210 and then Is_Private_Type (Etype (Exp))
1211 and then Present (Full_View (Etype (Exp)))
1212 and then Is_Discrete_Type (Full_View (Etype (Exp)))
1213 then
1214 Resolve (Exp, Etype (Exp));
1215 Exp_Type := Full_View (Etype (Exp));
1217 else
1218 Analyze_And_Resolve (Exp, Any_Discrete);
1219 Exp_Type := Etype (Exp);
1220 end if;
1222 Check_Unset_Reference (Exp);
1223 Exp_Btype := Base_Type (Exp_Type);
1225 -- The expression must be of a discrete type which must be determinable
1226 -- independently of the context in which the expression occurs, but
1227 -- using the fact that the expression must be of a discrete type.
1228 -- Moreover, the type this expression must not be a character literal
1229 -- (which is always ambiguous) or, for Ada-83, a generic formal type.
1231 -- If error already reported by Resolve, nothing more to do
1233 if Exp_Btype = Any_Discrete or else Exp_Btype = Any_Type then
1234 return;
1236 elsif Exp_Btype = Any_Character then
1237 Error_Msg_N
1238 ("character literal as case expression is ambiguous", Exp);
1239 return;
1241 elsif Ada_Version = Ada_83
1242 and then (Is_Generic_Type (Exp_Btype)
1243 or else Is_Generic_Type (Root_Type (Exp_Btype)))
1244 then
1245 Error_Msg_N
1246 ("(Ada 83) case expression cannot be of a generic type", Exp);
1247 return;
1248 end if;
1250 -- If the case expression is a formal object of mode in out, then treat
1251 -- it as having a nonstatic subtype by forcing use of the base type
1252 -- (which has to get passed to Check_Case_Choices below). Also use base
1253 -- type when the case expression is parenthesized.
1255 if Paren_Count (Exp) > 0
1256 or else (Is_Entity_Name (Exp)
1257 and then Ekind (Entity (Exp)) = E_Generic_In_Out_Parameter)
1258 then
1259 Exp_Type := Exp_Btype;
1260 end if;
1262 -- Call instantiated procedures to analyzwe and check discrete choices
1264 Analyze_Choices (Alternatives (N), Exp_Type);
1265 Check_Choices (N, Alternatives (N), Exp_Type, Others_Present);
1267 -- Case statement with single OTHERS alternative not allowed in SPARK
1269 if Others_Present and then List_Length (Alternatives (N)) = 1 then
1270 Check_SPARK_05_Restriction
1271 ("OTHERS as unique case alternative is not allowed", N);
1272 end if;
1274 if Exp_Type = Universal_Integer and then not Others_Present then
1275 Error_Msg_N ("case on universal integer requires OTHERS choice", Exp);
1276 end if;
1278 -- If all our exits were blocked by unconditional transfers of control,
1279 -- then the entire CASE statement acts as an unconditional transfer of
1280 -- control, so treat it like one, and check unreachable code. Skip this
1281 -- test if we had serious errors preventing any statement analysis.
1283 if Unblocked_Exit_Count = 0 and then Statements_Analyzed then
1284 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1285 Check_Unreachable_Code (N);
1286 else
1287 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1288 end if;
1290 -- If the expander is active it will detect the case of a statically
1291 -- determined single alternative and remove warnings for the case, but
1292 -- if we are not doing expansion, that circuit won't be active. Here we
1293 -- duplicate the effect of removing warnings in the same way, so that
1294 -- we will get the same set of warnings in -gnatc mode.
1296 if not Expander_Active
1297 and then Compile_Time_Known_Value (Expression (N))
1298 and then Serious_Errors_Detected = 0
1299 then
1300 declare
1301 Chosen : constant Node_Id := Find_Static_Alternative (N);
1302 Alt : Node_Id;
1304 begin
1305 Alt := First (Alternatives (N));
1306 while Present (Alt) loop
1307 if Alt /= Chosen then
1308 Remove_Warning_Messages (Statements (Alt));
1309 end if;
1311 Next (Alt);
1312 end loop;
1313 end;
1314 end if;
1315 end Analyze_Case_Statement;
1317 ----------------------------
1318 -- Analyze_Exit_Statement --
1319 ----------------------------
1321 -- If the exit includes a name, it must be the name of a currently open
1322 -- loop. Otherwise there must be an innermost open loop on the stack, to
1323 -- which the statement implicitly refers.
1325 -- Additionally, in SPARK mode:
1327 -- The exit can only name the closest enclosing loop;
1329 -- An exit with a when clause must be directly contained in a loop;
1331 -- An exit without a when clause must be directly contained in an
1332 -- if-statement with no elsif or else, which is itself directly contained
1333 -- in a loop. The exit must be the last statement in the if-statement.
1335 procedure Analyze_Exit_Statement (N : Node_Id) is
1336 Target : constant Node_Id := Name (N);
1337 Cond : constant Node_Id := Condition (N);
1338 Scope_Id : Entity_Id;
1339 U_Name : Entity_Id;
1340 Kind : Entity_Kind;
1342 begin
1343 if No (Cond) then
1344 Check_Unreachable_Code (N);
1345 end if;
1347 if Present (Target) then
1348 Analyze (Target);
1349 U_Name := Entity (Target);
1351 if not In_Open_Scopes (U_Name) or else Ekind (U_Name) /= E_Loop then
1352 Error_Msg_N ("invalid loop name in exit statement", N);
1353 return;
1355 else
1356 if Has_Loop_In_Inner_Open_Scopes (U_Name) then
1357 Check_SPARK_05_Restriction
1358 ("exit label must name the closest enclosing loop", N);
1359 end if;
1361 Set_Has_Exit (U_Name);
1362 end if;
1364 else
1365 U_Name := Empty;
1366 end if;
1368 for J in reverse 0 .. Scope_Stack.Last loop
1369 Scope_Id := Scope_Stack.Table (J).Entity;
1370 Kind := Ekind (Scope_Id);
1372 if Kind = E_Loop and then (No (Target) or else Scope_Id = U_Name) then
1373 Set_Has_Exit (Scope_Id);
1374 exit;
1376 elsif Kind = E_Block
1377 or else Kind = E_Loop
1378 or else Kind = E_Return_Statement
1379 then
1380 null;
1382 else
1383 Error_Msg_N
1384 ("cannot exit from program unit or accept statement", N);
1385 return;
1386 end if;
1387 end loop;
1389 -- Verify that if present the condition is a Boolean expression
1391 if Present (Cond) then
1392 Analyze_And_Resolve (Cond, Any_Boolean);
1393 Check_Unset_Reference (Cond);
1394 end if;
1396 -- In SPARK mode, verify that the exit statement respects the SPARK
1397 -- restrictions.
1399 if Present (Cond) then
1400 if Nkind (Parent (N)) /= N_Loop_Statement then
1401 Check_SPARK_05_Restriction
1402 ("exit with when clause must be directly in loop", N);
1403 end if;
1405 else
1406 if Nkind (Parent (N)) /= N_If_Statement then
1407 if Nkind (Parent (N)) = N_Elsif_Part then
1408 Check_SPARK_05_Restriction
1409 ("exit must be in IF without ELSIF", N);
1410 else
1411 Check_SPARK_05_Restriction ("exit must be directly in IF", N);
1412 end if;
1414 elsif Nkind (Parent (Parent (N))) /= N_Loop_Statement then
1415 Check_SPARK_05_Restriction
1416 ("exit must be in IF directly in loop", N);
1418 -- First test the presence of ELSE, so that an exit in an ELSE leads
1419 -- to an error mentioning the ELSE.
1421 elsif Present (Else_Statements (Parent (N))) then
1422 Check_SPARK_05_Restriction ("exit must be in IF without ELSE", N);
1424 -- An exit in an ELSIF does not reach here, as it would have been
1425 -- detected in the case (Nkind (Parent (N)) /= N_If_Statement).
1427 elsif Present (Elsif_Parts (Parent (N))) then
1428 Check_SPARK_05_Restriction ("exit must be in IF without ELSIF", N);
1429 end if;
1430 end if;
1432 -- Chain exit statement to associated loop entity
1434 Set_Next_Exit_Statement (N, First_Exit_Statement (Scope_Id));
1435 Set_First_Exit_Statement (Scope_Id, N);
1437 -- Since the exit may take us out of a loop, any previous assignment
1438 -- statement is not useless, so clear last assignment indications. It
1439 -- is OK to keep other current values, since if the exit statement
1440 -- does not exit, then the current values are still valid.
1442 Kill_Current_Values (Last_Assignment_Only => True);
1443 end Analyze_Exit_Statement;
1445 ----------------------------
1446 -- Analyze_Goto_Statement --
1447 ----------------------------
1449 procedure Analyze_Goto_Statement (N : Node_Id) is
1450 Label : constant Node_Id := Name (N);
1451 Scope_Id : Entity_Id;
1452 Label_Scope : Entity_Id;
1453 Label_Ent : Entity_Id;
1455 begin
1456 Check_SPARK_05_Restriction ("goto statement is not allowed", N);
1458 -- Actual semantic checks
1460 Check_Unreachable_Code (N);
1461 Kill_Current_Values (Last_Assignment_Only => True);
1463 Analyze (Label);
1464 Label_Ent := Entity (Label);
1466 -- Ignore previous error
1468 if Label_Ent = Any_Id then
1469 Check_Error_Detected;
1470 return;
1472 -- We just have a label as the target of a goto
1474 elsif Ekind (Label_Ent) /= E_Label then
1475 Error_Msg_N ("target of goto statement must be a label", Label);
1476 return;
1478 -- Check that the target of the goto is reachable according to Ada
1479 -- scoping rules. Note: the special gotos we generate for optimizing
1480 -- local handling of exceptions would violate these rules, but we mark
1481 -- such gotos as analyzed when built, so this code is never entered.
1483 elsif not Reachable (Label_Ent) then
1484 Error_Msg_N ("target of goto statement is not reachable", Label);
1485 return;
1486 end if;
1488 -- Here if goto passes initial validity checks
1490 Label_Scope := Enclosing_Scope (Label_Ent);
1492 for J in reverse 0 .. Scope_Stack.Last loop
1493 Scope_Id := Scope_Stack.Table (J).Entity;
1495 if Label_Scope = Scope_Id
1496 or else not Ekind_In (Scope_Id, E_Block, E_Loop, E_Return_Statement)
1497 then
1498 if Scope_Id /= Label_Scope then
1499 Error_Msg_N
1500 ("cannot exit from program unit or accept statement", N);
1501 end if;
1503 return;
1504 end if;
1505 end loop;
1507 raise Program_Error;
1508 end Analyze_Goto_Statement;
1510 --------------------------
1511 -- Analyze_If_Statement --
1512 --------------------------
1514 -- A special complication arises in the analysis of if statements
1516 -- The expander has circuitry to completely delete code that it can tell
1517 -- will not be executed (as a result of compile time known conditions). In
1518 -- the analyzer, we ensure that code that will be deleted in this manner
1519 -- is analyzed but not expanded. This is obviously more efficient, but
1520 -- more significantly, difficulties arise if code is expanded and then
1521 -- eliminated (e.g. exception table entries disappear). Similarly, itypes
1522 -- generated in deleted code must be frozen from start, because the nodes
1523 -- on which they depend will not be available at the freeze point.
1525 procedure Analyze_If_Statement (N : Node_Id) is
1526 E : Node_Id;
1528 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1529 -- Recursively save value of this global, will be restored on exit
1531 Save_In_Deleted_Code : Boolean;
1533 Del : Boolean := False;
1534 -- This flag gets set True if a True condition has been found, which
1535 -- means that remaining ELSE/ELSIF parts are deleted.
1537 procedure Analyze_Cond_Then (Cnode : Node_Id);
1538 -- This is applied to either the N_If_Statement node itself or to an
1539 -- N_Elsif_Part node. It deals with analyzing the condition and the THEN
1540 -- statements associated with it.
1542 -----------------------
1543 -- Analyze_Cond_Then --
1544 -----------------------
1546 procedure Analyze_Cond_Then (Cnode : Node_Id) is
1547 Cond : constant Node_Id := Condition (Cnode);
1548 Tstm : constant List_Id := Then_Statements (Cnode);
1550 begin
1551 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1552 Analyze_And_Resolve (Cond, Any_Boolean);
1553 Check_Unset_Reference (Cond);
1554 Set_Current_Value_Condition (Cnode);
1556 -- If already deleting, then just analyze then statements
1558 if Del then
1559 Analyze_Statements (Tstm);
1561 -- Compile time known value, not deleting yet
1563 elsif Compile_Time_Known_Value (Cond) then
1564 Save_In_Deleted_Code := In_Deleted_Code;
1566 -- If condition is True, then analyze the THEN statements and set
1567 -- no expansion for ELSE and ELSIF parts.
1569 if Is_True (Expr_Value (Cond)) then
1570 Analyze_Statements (Tstm);
1571 Del := True;
1572 Expander_Mode_Save_And_Set (False);
1573 In_Deleted_Code := True;
1575 -- If condition is False, analyze THEN with expansion off
1577 else -- Is_False (Expr_Value (Cond))
1578 Expander_Mode_Save_And_Set (False);
1579 In_Deleted_Code := True;
1580 Analyze_Statements (Tstm);
1581 Expander_Mode_Restore;
1582 In_Deleted_Code := Save_In_Deleted_Code;
1583 end if;
1585 -- Not known at compile time, not deleting, normal analysis
1587 else
1588 Analyze_Statements (Tstm);
1589 end if;
1590 end Analyze_Cond_Then;
1592 -- Start of processing for Analyze_If_Statement
1594 begin
1595 -- Initialize exit count for else statements. If there is no else part,
1596 -- this count will stay non-zero reflecting the fact that the uncovered
1597 -- else case is an unblocked exit.
1599 Unblocked_Exit_Count := 1;
1600 Analyze_Cond_Then (N);
1602 -- Now to analyze the elsif parts if any are present
1604 if Present (Elsif_Parts (N)) then
1605 E := First (Elsif_Parts (N));
1606 while Present (E) loop
1607 Analyze_Cond_Then (E);
1608 Next (E);
1609 end loop;
1610 end if;
1612 if Present (Else_Statements (N)) then
1613 Analyze_Statements (Else_Statements (N));
1614 end if;
1616 -- If all our exits were blocked by unconditional transfers of control,
1617 -- then the entire IF statement acts as an unconditional transfer of
1618 -- control, so treat it like one, and check unreachable code.
1620 if Unblocked_Exit_Count = 0 then
1621 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1622 Check_Unreachable_Code (N);
1623 else
1624 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1625 end if;
1627 if Del then
1628 Expander_Mode_Restore;
1629 In_Deleted_Code := Save_In_Deleted_Code;
1630 end if;
1632 if not Expander_Active
1633 and then Compile_Time_Known_Value (Condition (N))
1634 and then Serious_Errors_Detected = 0
1635 then
1636 if Is_True (Expr_Value (Condition (N))) then
1637 Remove_Warning_Messages (Else_Statements (N));
1639 if Present (Elsif_Parts (N)) then
1640 E := First (Elsif_Parts (N));
1641 while Present (E) loop
1642 Remove_Warning_Messages (Then_Statements (E));
1643 Next (E);
1644 end loop;
1645 end if;
1647 else
1648 Remove_Warning_Messages (Then_Statements (N));
1649 end if;
1650 end if;
1652 -- Warn on redundant if statement that has no effect
1654 -- Note, we could also check empty ELSIF parts ???
1656 if Warn_On_Redundant_Constructs
1658 -- If statement must be from source
1660 and then Comes_From_Source (N)
1662 -- Condition must not have obvious side effect
1664 and then Has_No_Obvious_Side_Effects (Condition (N))
1666 -- No elsif parts of else part
1668 and then No (Elsif_Parts (N))
1669 and then No (Else_Statements (N))
1671 -- Then must be a single null statement
1673 and then List_Length (Then_Statements (N)) = 1
1674 then
1675 -- Go to original node, since we may have rewritten something as
1676 -- a null statement (e.g. a case we could figure the outcome of).
1678 declare
1679 T : constant Node_Id := First (Then_Statements (N));
1680 S : constant Node_Id := Original_Node (T);
1682 begin
1683 if Comes_From_Source (S) and then Nkind (S) = N_Null_Statement then
1684 Error_Msg_N ("if statement has no effect?r?", N);
1685 end if;
1686 end;
1687 end if;
1688 end Analyze_If_Statement;
1690 ----------------------------------------
1691 -- Analyze_Implicit_Label_Declaration --
1692 ----------------------------------------
1694 -- An implicit label declaration is generated in the innermost enclosing
1695 -- declarative part. This is done for labels, and block and loop names.
1697 -- Note: any changes in this routine may need to be reflected in
1698 -- Analyze_Label_Entity.
1700 procedure Analyze_Implicit_Label_Declaration (N : Node_Id) is
1701 Id : constant Node_Id := Defining_Identifier (N);
1702 begin
1703 Enter_Name (Id);
1704 Set_Ekind (Id, E_Label);
1705 Set_Etype (Id, Standard_Void_Type);
1706 Set_Enclosing_Scope (Id, Current_Scope);
1707 end Analyze_Implicit_Label_Declaration;
1709 ------------------------------
1710 -- Analyze_Iteration_Scheme --
1711 ------------------------------
1713 procedure Analyze_Iteration_Scheme (N : Node_Id) is
1714 Cond : Node_Id;
1715 Iter_Spec : Node_Id;
1716 Loop_Spec : Node_Id;
1718 begin
1719 -- For an infinite loop, there is no iteration scheme
1721 if No (N) then
1722 return;
1723 end if;
1725 Cond := Condition (N);
1726 Iter_Spec := Iterator_Specification (N);
1727 Loop_Spec := Loop_Parameter_Specification (N);
1729 if Present (Cond) then
1730 Analyze_And_Resolve (Cond, Any_Boolean);
1731 Check_Unset_Reference (Cond);
1732 Set_Current_Value_Condition (N);
1734 elsif Present (Iter_Spec) then
1735 Analyze_Iterator_Specification (Iter_Spec);
1737 else
1738 Analyze_Loop_Parameter_Specification (Loop_Spec);
1739 end if;
1740 end Analyze_Iteration_Scheme;
1742 ------------------------------------
1743 -- Analyze_Iterator_Specification --
1744 ------------------------------------
1746 procedure Analyze_Iterator_Specification (N : Node_Id) is
1747 Loc : constant Source_Ptr := Sloc (N);
1748 Def_Id : constant Node_Id := Defining_Identifier (N);
1749 Subt : constant Node_Id := Subtype_Indication (N);
1750 Iter_Name : constant Node_Id := Name (N);
1752 Ent : Entity_Id;
1753 Typ : Entity_Id;
1754 Bas : Entity_Id;
1756 procedure Check_Reverse_Iteration (Typ : Entity_Id);
1757 -- For an iteration over a container, if the loop carries the Reverse
1758 -- indicator, verify that the container type has an Iterate aspect that
1759 -- implements the reversible iterator interface.
1761 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id;
1762 -- For containers with Iterator and related aspects, the cursor is
1763 -- obtained by locating an entity with the proper name in the scope
1764 -- of the type.
1766 -----------------------------
1767 -- Check_Reverse_Iteration --
1768 -----------------------------
1770 procedure Check_Reverse_Iteration (Typ : Entity_Id) is
1771 begin
1772 if Reverse_Present (N)
1773 and then not Is_Array_Type (Typ)
1774 and then not Is_Reversible_Iterator (Typ)
1775 then
1776 Error_Msg_NE
1777 ("container type does not support reverse iteration", N, Typ);
1778 end if;
1779 end Check_Reverse_Iteration;
1781 ---------------------
1782 -- Get_Cursor_Type --
1783 ---------------------
1785 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id is
1786 Ent : Entity_Id;
1788 begin
1789 Ent := First_Entity (Scope (Typ));
1790 while Present (Ent) loop
1791 exit when Chars (Ent) = Name_Cursor;
1792 Next_Entity (Ent);
1793 end loop;
1795 if No (Ent) then
1796 return Any_Type;
1797 end if;
1799 -- The cursor is the target of generated assignments in the
1800 -- loop, and cannot have a limited type.
1802 if Is_Limited_Type (Etype (Ent)) then
1803 Error_Msg_N ("cursor type cannot be limited", N);
1804 end if;
1806 return Etype (Ent);
1807 end Get_Cursor_Type;
1809 -- Start of processing for Analyze_iterator_Specification
1811 begin
1812 Enter_Name (Def_Id);
1814 -- AI12-0151 specifies that when the subtype indication is present, it
1815 -- must statically match the type of the array or container element.
1816 -- To simplify this check, we introduce a subtype declaration with the
1817 -- given subtype indication when it carries a constraint, and rewrite
1818 -- the original as a reference to the created subtype entity.
1820 if Present (Subt) then
1821 if Nkind (Subt) = N_Subtype_Indication then
1822 declare
1823 S : constant Entity_Id := Make_Temporary (Sloc (Subt), 'S');
1824 Decl : constant Node_Id :=
1825 Make_Subtype_Declaration (Loc,
1826 Defining_Identifier => S,
1827 Subtype_Indication => New_Copy_Tree (Subt));
1828 begin
1829 Insert_Before (Parent (Parent (N)), Decl);
1830 Analyze (Decl);
1831 Rewrite (Subt, New_Occurrence_Of (S, Sloc (Subt)));
1832 end;
1833 else
1834 Analyze (Subt);
1835 end if;
1837 -- Save entity of subtype indication for subsequent check
1839 Bas := Entity (Subt);
1840 end if;
1842 Preanalyze_Range (Iter_Name);
1844 -- Set the kind of the loop variable, which is not visible within
1845 -- the iterator name.
1847 Set_Ekind (Def_Id, E_Variable);
1849 -- Provide a link between the iterator variable and the container, for
1850 -- subsequent use in cross-reference and modification information.
1852 if Of_Present (N) then
1853 Set_Related_Expression (Def_Id, Iter_Name);
1855 -- For a container, the iterator is specified through the aspect
1857 if not Is_Array_Type (Etype (Iter_Name)) then
1858 declare
1859 Iterator : constant Entity_Id :=
1860 Find_Value_Of_Aspect
1861 (Etype (Iter_Name), Aspect_Default_Iterator);
1863 I : Interp_Index;
1864 It : Interp;
1866 begin
1867 if No (Iterator) then
1868 null; -- error reported below.
1870 elsif not Is_Overloaded (Iterator) then
1871 Check_Reverse_Iteration (Etype (Iterator));
1873 -- If Iterator is overloaded, use reversible iterator if
1874 -- one is available.
1876 elsif Is_Overloaded (Iterator) then
1877 Get_First_Interp (Iterator, I, It);
1878 while Present (It.Nam) loop
1879 if Ekind (It.Nam) = E_Function
1880 and then Is_Reversible_Iterator (Etype (It.Nam))
1881 then
1882 Set_Etype (Iterator, It.Typ);
1883 Set_Entity (Iterator, It.Nam);
1884 exit;
1885 end if;
1887 Get_Next_Interp (I, It);
1888 end loop;
1890 Check_Reverse_Iteration (Etype (Iterator));
1891 end if;
1892 end;
1893 end if;
1894 end if;
1896 -- If the domain of iteration is an expression, create a declaration for
1897 -- it, so that finalization actions are introduced outside of the loop.
1898 -- The declaration must be a renaming because the body of the loop may
1899 -- assign to elements.
1901 if not Is_Entity_Name (Iter_Name)
1903 -- When the context is a quantified expression, the renaming
1904 -- declaration is delayed until the expansion phase if we are
1905 -- doing expansion.
1907 and then (Nkind (Parent (N)) /= N_Quantified_Expression
1908 or else Operating_Mode = Check_Semantics)
1910 -- Do not perform this expansion in SPARK mode, since the formal
1911 -- verification directly deals with the source form of the iterator.
1912 -- Ditto for ASIS, where the temporary may hide the transformation
1913 -- of a selected component into a prefixed function call.
1915 and then not GNATprove_Mode
1916 and then not ASIS_Mode
1917 then
1918 declare
1919 Id : constant Entity_Id := Make_Temporary (Loc, 'R', Iter_Name);
1920 Decl : Node_Id;
1921 Act_S : Node_Id;
1923 begin
1925 -- If the domain of iteration is an array component that depends
1926 -- on a discriminant, create actual subtype for it. Pre-analysis
1927 -- does not generate the actual subtype of a selected component.
1929 if Nkind (Iter_Name) = N_Selected_Component
1930 and then Is_Array_Type (Etype (Iter_Name))
1931 then
1932 Act_S :=
1933 Build_Actual_Subtype_Of_Component
1934 (Etype (Selector_Name (Iter_Name)), Iter_Name);
1935 Insert_Action (N, Act_S);
1937 if Present (Act_S) then
1938 Typ := Defining_Identifier (Act_S);
1939 else
1940 Typ := Etype (Iter_Name);
1941 end if;
1943 else
1944 Typ := Etype (Iter_Name);
1946 -- Verify that the expression produces an iterator
1948 if not Of_Present (N) and then not Is_Iterator (Typ)
1949 and then not Is_Array_Type (Typ)
1950 and then No (Find_Aspect (Typ, Aspect_Iterable))
1951 then
1952 Error_Msg_N
1953 ("expect object that implements iterator interface",
1954 Iter_Name);
1955 end if;
1956 end if;
1958 -- Protect against malformed iterator
1960 if Typ = Any_Type then
1961 Error_Msg_N ("invalid expression in loop iterator", Iter_Name);
1962 return;
1963 end if;
1965 if not Of_Present (N) then
1966 Check_Reverse_Iteration (Typ);
1967 end if;
1969 -- The name in the renaming declaration may be a function call.
1970 -- Indicate that it does not come from source, to suppress
1971 -- spurious warnings on renamings of parameterless functions,
1972 -- a common enough idiom in user-defined iterators.
1974 Decl :=
1975 Make_Object_Renaming_Declaration (Loc,
1976 Defining_Identifier => Id,
1977 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
1978 Name =>
1979 New_Copy_Tree (Iter_Name, New_Sloc => Loc));
1981 -- Create a transient scope to ensure that all the temporaries
1982 -- generated by Remove_Side_Effects as part of processing this
1983 -- renaming declaration (if any) are attached by Insert_Actions
1984 -- to it. It has no effect on the generated code if no actions
1985 -- are added to it (see Wrap_Transient_Declaration).
1987 if Expander_Active then
1988 Establish_Transient_Scope (Name (Decl), Sec_Stack => True);
1989 end if;
1991 Insert_Actions (Parent (Parent (N)), New_List (Decl));
1992 Rewrite (Name (N), New_Occurrence_Of (Id, Loc));
1993 Set_Etype (Id, Typ);
1994 Set_Etype (Name (N), Typ);
1995 end;
1997 -- Container is an entity or an array with uncontrolled components, or
1998 -- else it is a container iterator given by a function call, typically
1999 -- called Iterate in the case of predefined containers, even though
2000 -- Iterate is not a reserved name. What matters is that the return type
2001 -- of the function is an iterator type.
2003 elsif Is_Entity_Name (Iter_Name) then
2004 Analyze (Iter_Name);
2006 if Nkind (Iter_Name) = N_Function_Call then
2007 declare
2008 C : constant Node_Id := Name (Iter_Name);
2009 I : Interp_Index;
2010 It : Interp;
2012 begin
2013 if not Is_Overloaded (Iter_Name) then
2014 Resolve (Iter_Name, Etype (C));
2016 else
2017 Get_First_Interp (C, I, It);
2018 while It.Typ /= Empty loop
2019 if Reverse_Present (N) then
2020 if Is_Reversible_Iterator (It.Typ) then
2021 Resolve (Iter_Name, It.Typ);
2022 exit;
2023 end if;
2025 elsif Is_Iterator (It.Typ) then
2026 Resolve (Iter_Name, It.Typ);
2027 exit;
2028 end if;
2030 Get_Next_Interp (I, It);
2031 end loop;
2032 end if;
2033 end;
2035 -- Domain of iteration is not overloaded
2037 else
2038 Resolve (Iter_Name, Etype (Iter_Name));
2039 end if;
2041 if not Of_Present (N) then
2042 Check_Reverse_Iteration (Etype (Iter_Name));
2043 end if;
2044 end if;
2046 -- Get base type of container, for proper retrieval of Cursor type
2047 -- and primitive operations.
2049 Typ := Base_Type (Etype (Iter_Name));
2051 if Is_Array_Type (Typ) then
2052 if Of_Present (N) then
2053 Set_Etype (Def_Id, Component_Type (Typ));
2055 -- The loop variable is aliased if the array components are
2056 -- aliased.
2058 Set_Is_Aliased (Def_Id, Has_Aliased_Components (Typ));
2060 -- AI12-0151 stipulates that the container cannot be a component
2061 -- that depends on a discriminant if the enclosing object is
2062 -- mutable, to prevent a modification of the container in the
2063 -- course of an iteration.
2065 -- Should comment on need to go to Original_Node ???
2067 if Nkind (Original_Node (Iter_Name)) = N_Selected_Component
2068 and then Is_Dependent_Component_Of_Mutable_Object
2069 (Original_Node (Iter_Name))
2070 then
2071 Error_Msg_N
2072 ("container cannot be a discriminant-dependent "
2073 & "component of a mutable object", N);
2074 end if;
2076 if Present (Subt)
2077 and then
2078 (Base_Type (Bas) /= Base_Type (Component_Type (Typ))
2079 or else
2080 not Subtypes_Statically_Match (Bas, Component_Type (Typ)))
2081 then
2082 Error_Msg_N
2083 ("subtype indication does not match component type", Subt);
2084 end if;
2086 -- Here we have a missing Range attribute
2088 else
2089 Error_Msg_N
2090 ("missing Range attribute in iteration over an array", N);
2092 -- In Ada 2012 mode, this may be an attempt at an iterator
2094 if Ada_Version >= Ada_2012 then
2095 Error_Msg_NE
2096 ("\if& is meant to designate an element of the array, use OF",
2097 N, Def_Id);
2098 end if;
2100 -- Prevent cascaded errors
2102 Set_Ekind (Def_Id, E_Loop_Parameter);
2103 Set_Etype (Def_Id, Etype (First_Index (Typ)));
2104 end if;
2106 -- Check for type error in iterator
2108 elsif Typ = Any_Type then
2109 return;
2111 -- Iteration over a container
2113 else
2114 Set_Ekind (Def_Id, E_Loop_Parameter);
2115 Error_Msg_Ada_2012_Feature ("container iterator", Sloc (N));
2117 -- OF present
2119 if Of_Present (N) then
2120 if Has_Aspect (Typ, Aspect_Iterable) then
2121 declare
2122 Elt : constant Entity_Id :=
2123 Get_Iterable_Type_Primitive (Typ, Name_Element);
2124 begin
2125 if No (Elt) then
2126 Error_Msg_N
2127 ("missing Element primitive for iteration", N);
2128 else
2129 Set_Etype (Def_Id, Etype (Elt));
2130 end if;
2131 end;
2133 -- For a predefined container, The type of the loop variable is
2134 -- the Iterator_Element aspect of the container type.
2136 else
2137 declare
2138 Element : constant Entity_Id :=
2139 Find_Value_Of_Aspect (Typ, Aspect_Iterator_Element);
2140 Iterator : constant Entity_Id :=
2141 Find_Value_Of_Aspect (Typ, Aspect_Default_Iterator);
2142 Cursor_Type : Entity_Id;
2144 begin
2145 if No (Element) then
2146 Error_Msg_NE ("cannot iterate over&", N, Typ);
2147 return;
2149 else
2150 Set_Etype (Def_Id, Entity (Element));
2151 Cursor_Type := Get_Cursor_Type (Typ);
2152 pragma Assert (Present (Cursor_Type));
2154 -- If subtype indication was given, verify that it covers
2155 -- the element type of the container.
2157 if Present (Subt)
2158 and then (not Covers (Bas, Etype (Def_Id))
2159 or else not Subtypes_Statically_Match
2160 (Bas, Etype (Def_Id)))
2161 then
2162 Error_Msg_N
2163 ("subtype indication does not match element type",
2164 Subt);
2165 end if;
2167 -- If the container has a variable indexing aspect, the
2168 -- element is a variable and is modifiable in the loop.
2170 if Has_Aspect (Typ, Aspect_Variable_Indexing) then
2171 Set_Ekind (Def_Id, E_Variable);
2172 end if;
2174 -- If the container is a constant, iterating over it
2175 -- requires a Constant_Indexing operation.
2177 if not Is_Variable (Iter_Name)
2178 and then not Has_Aspect (Typ, Aspect_Constant_Indexing)
2179 then
2180 Error_Msg_N ("iteration over constant container "
2181 & "require constant_indexing aspect", N);
2183 -- The Iterate function may have an in_out parameter,
2184 -- and a constant container is thus illegal.
2186 elsif Present (Iterator)
2187 and then Ekind (Entity (Iterator)) = E_Function
2188 and then Ekind (First_Formal (Entity (Iterator))) /=
2189 E_In_Parameter
2190 and then not Is_Variable (Iter_Name)
2191 then
2192 Error_Msg_N
2193 ("variable container expected", N);
2194 end if;
2196 if Nkind (Original_Node (Iter_Name))
2197 = N_Selected_Component
2198 and then
2199 Is_Dependent_Component_Of_Mutable_Object
2200 (Original_Node (Iter_Name))
2201 then
2202 Error_Msg_N
2203 ("container cannot be a discriminant-dependent "
2204 & "component of a mutable object", N);
2205 end if;
2206 end if;
2207 end;
2208 end if;
2210 -- IN iterator, domain is a range, or a call to Iterate function
2212 else
2213 -- For an iteration of the form IN, the name must denote an
2214 -- iterator, typically the result of a call to Iterate. Give a
2215 -- useful error message when the name is a container by itself.
2217 -- The type may be a formal container type, which has to have
2218 -- an Iterable aspect detailing the required primitives.
2220 if Is_Entity_Name (Original_Node (Name (N)))
2221 and then not Is_Iterator (Typ)
2222 then
2223 if Has_Aspect (Typ, Aspect_Iterable) then
2224 null;
2226 elsif not Has_Aspect (Typ, Aspect_Iterator_Element) then
2227 Error_Msg_NE
2228 ("cannot iterate over&", Name (N), Typ);
2229 else
2230 Error_Msg_N
2231 ("name must be an iterator, not a container", Name (N));
2232 end if;
2234 if Has_Aspect (Typ, Aspect_Iterable) then
2235 null;
2236 else
2237 Error_Msg_NE
2238 ("\to iterate directly over the elements of a container, "
2239 & "write `of &`", Name (N), Original_Node (Name (N)));
2241 -- No point in continuing analysis of iterator spec
2243 return;
2244 end if;
2245 end if;
2247 -- If the name is a call (typically prefixed) to some Iterate
2248 -- function, it has been rewritten as an object declaration.
2249 -- If that object is a selected component, verify that it is not
2250 -- a component of an unconstrained mutable object.
2252 if Nkind (Iter_Name) = N_Identifier then
2253 declare
2254 Orig_Node : constant Node_Id := Original_Node (Iter_Name);
2255 Iter_Kind : constant Node_Kind := Nkind (Orig_Node);
2256 Obj : Node_Id;
2258 begin
2259 if Iter_Kind = N_Selected_Component then
2260 Obj := Prefix (Orig_Node);
2262 elsif Iter_Kind = N_Function_Call then
2263 Obj := First_Actual (Orig_Node);
2265 -- If neither, the name comes from source
2267 else
2268 Obj := Iter_Name;
2269 end if;
2271 if Nkind (Obj) = N_Selected_Component
2272 and then Is_Dependent_Component_Of_Mutable_Object (Obj)
2273 then
2274 Error_Msg_N
2275 ("container cannot be a discriminant-dependent "
2276 & "component of a mutable object", N);
2277 end if;
2278 end;
2279 end if;
2281 -- The result type of Iterate function is the classwide type of
2282 -- the interface parent. We need the specific Cursor type defined
2283 -- in the container package. We obtain it by name for a predefined
2284 -- container, or through the Iterable aspect for a formal one.
2286 if Has_Aspect (Typ, Aspect_Iterable) then
2287 Set_Etype (Def_Id,
2288 Get_Cursor_Type
2289 (Parent (Find_Value_Of_Aspect (Typ, Aspect_Iterable)),
2290 Typ));
2291 Ent := Etype (Def_Id);
2293 else
2294 Set_Etype (Def_Id, Get_Cursor_Type (Typ));
2295 end if;
2297 end if;
2298 end if;
2300 -- A loop parameter cannot be effectively volatile (SPARK RM 7.1.3(4)).
2301 -- This check is relevant only when SPARK_Mode is on as it is not a
2302 -- standard Ada legality check.
2304 -- Not clear whether this applies to element iterators, where the
2305 -- cursor is not an explicit entity ???
2307 if SPARK_Mode = On
2308 and then not Of_Present (N)
2309 and then Is_Effectively_Volatile (Ent)
2310 then
2311 Error_Msg_N ("loop parameter cannot be volatile", Ent);
2312 end if;
2313 end Analyze_Iterator_Specification;
2315 -------------------
2316 -- Analyze_Label --
2317 -------------------
2319 -- Note: the semantic work required for analyzing labels (setting them as
2320 -- reachable) was done in a prepass through the statements in the block,
2321 -- so that forward gotos would be properly handled. See Analyze_Statements
2322 -- for further details. The only processing required here is to deal with
2323 -- optimizations that depend on an assumption of sequential control flow,
2324 -- since of course the occurrence of a label breaks this assumption.
2326 procedure Analyze_Label (N : Node_Id) is
2327 pragma Warnings (Off, N);
2328 begin
2329 Kill_Current_Values;
2330 end Analyze_Label;
2332 --------------------------
2333 -- Analyze_Label_Entity --
2334 --------------------------
2336 procedure Analyze_Label_Entity (E : Entity_Id) is
2337 begin
2338 Set_Ekind (E, E_Label);
2339 Set_Etype (E, Standard_Void_Type);
2340 Set_Enclosing_Scope (E, Current_Scope);
2341 Set_Reachable (E, True);
2342 end Analyze_Label_Entity;
2344 ------------------------------------------
2345 -- Analyze_Loop_Parameter_Specification --
2346 ------------------------------------------
2348 procedure Analyze_Loop_Parameter_Specification (N : Node_Id) is
2349 Loop_Nod : constant Node_Id := Parent (Parent (N));
2351 procedure Check_Controlled_Array_Attribute (DS : Node_Id);
2352 -- If the bounds are given by a 'Range reference on a function call
2353 -- that returns a controlled array, introduce an explicit declaration
2354 -- to capture the bounds, so that the function result can be finalized
2355 -- in timely fashion.
2357 procedure Check_Predicate_Use (T : Entity_Id);
2358 -- Diagnose Attempt to iterate through non-static predicate. Note that
2359 -- a type with inherited predicates may have both static and dynamic
2360 -- forms. In this case it is not sufficent to check the static predicate
2361 -- function only, look for a dynamic predicate aspect as well.
2363 function Has_Call_Using_Secondary_Stack (N : Node_Id) return Boolean;
2364 -- N is the node for an arbitrary construct. This function searches the
2365 -- construct N to see if any expressions within it contain function
2366 -- calls that use the secondary stack, returning True if any such call
2367 -- is found, and False otherwise.
2369 procedure Process_Bounds (R : Node_Id);
2370 -- If the iteration is given by a range, create temporaries and
2371 -- assignment statements block to capture the bounds and perform
2372 -- required finalization actions in case a bound includes a function
2373 -- call that uses the temporary stack. We first pre-analyze a copy of
2374 -- the range in order to determine the expected type, and analyze and
2375 -- resolve the original bounds.
2377 --------------------------------------
2378 -- Check_Controlled_Array_Attribute --
2379 --------------------------------------
2381 procedure Check_Controlled_Array_Attribute (DS : Node_Id) is
2382 begin
2383 if Nkind (DS) = N_Attribute_Reference
2384 and then Is_Entity_Name (Prefix (DS))
2385 and then Ekind (Entity (Prefix (DS))) = E_Function
2386 and then Is_Array_Type (Etype (Entity (Prefix (DS))))
2387 and then
2388 Is_Controlled (Component_Type (Etype (Entity (Prefix (DS)))))
2389 and then Expander_Active
2390 then
2391 declare
2392 Loc : constant Source_Ptr := Sloc (N);
2393 Arr : constant Entity_Id := Etype (Entity (Prefix (DS)));
2394 Indx : constant Entity_Id :=
2395 Base_Type (Etype (First_Index (Arr)));
2396 Subt : constant Entity_Id := Make_Temporary (Loc, 'S');
2397 Decl : Node_Id;
2399 begin
2400 Decl :=
2401 Make_Subtype_Declaration (Loc,
2402 Defining_Identifier => Subt,
2403 Subtype_Indication =>
2404 Make_Subtype_Indication (Loc,
2405 Subtype_Mark => New_Occurrence_Of (Indx, Loc),
2406 Constraint =>
2407 Make_Range_Constraint (Loc, Relocate_Node (DS))));
2408 Insert_Before (Loop_Nod, Decl);
2409 Analyze (Decl);
2411 Rewrite (DS,
2412 Make_Attribute_Reference (Loc,
2413 Prefix => New_Occurrence_Of (Subt, Loc),
2414 Attribute_Name => Attribute_Name (DS)));
2416 Analyze (DS);
2417 end;
2418 end if;
2419 end Check_Controlled_Array_Attribute;
2421 -------------------------
2422 -- Check_Predicate_Use --
2423 -------------------------
2425 procedure Check_Predicate_Use (T : Entity_Id) is
2426 begin
2427 -- A predicated subtype is illegal in loops and related constructs
2428 -- if the predicate is not static, or if it is a non-static subtype
2429 -- of a statically predicated subtype.
2431 if Is_Discrete_Type (T)
2432 and then Has_Predicates (T)
2433 and then (not Has_Static_Predicate (T)
2434 or else not Is_Static_Subtype (T)
2435 or else Has_Dynamic_Predicate_Aspect (T))
2436 then
2437 -- Seems a confusing message for the case of a static predicate
2438 -- with a non-static subtype???
2440 Bad_Predicated_Subtype_Use
2441 ("cannot use subtype& with non-static predicate for loop "
2442 & "iteration", Discrete_Subtype_Definition (N),
2443 T, Suggest_Static => True);
2445 elsif Inside_A_Generic and then Is_Generic_Formal (T) then
2446 Set_No_Dynamic_Predicate_On_Actual (T);
2447 end if;
2448 end Check_Predicate_Use;
2450 ------------------------------------
2451 -- Has_Call_Using_Secondary_Stack --
2452 ------------------------------------
2454 function Has_Call_Using_Secondary_Stack (N : Node_Id) return Boolean is
2456 function Check_Call (N : Node_Id) return Traverse_Result;
2457 -- Check if N is a function call which uses the secondary stack
2459 ----------------
2460 -- Check_Call --
2461 ----------------
2463 function Check_Call (N : Node_Id) return Traverse_Result is
2464 Nam : Node_Id;
2465 Subp : Entity_Id;
2466 Return_Typ : Entity_Id;
2468 begin
2469 if Nkind (N) = N_Function_Call then
2470 Nam := Name (N);
2472 -- Call using access to subprogram with explicit dereference
2474 if Nkind (Nam) = N_Explicit_Dereference then
2475 Subp := Etype (Nam);
2477 -- Call using a selected component notation or Ada 2005 object
2478 -- operation notation
2480 elsif Nkind (Nam) = N_Selected_Component then
2481 Subp := Entity (Selector_Name (Nam));
2483 -- Common case
2485 else
2486 Subp := Entity (Nam);
2487 end if;
2489 Return_Typ := Etype (Subp);
2491 if Is_Composite_Type (Return_Typ)
2492 and then not Is_Constrained (Return_Typ)
2493 then
2494 return Abandon;
2496 elsif Sec_Stack_Needed_For_Return (Subp) then
2497 return Abandon;
2498 end if;
2499 end if;
2501 -- Continue traversing the tree
2503 return OK;
2504 end Check_Call;
2506 function Check_Calls is new Traverse_Func (Check_Call);
2508 -- Start of processing for Has_Call_Using_Secondary_Stack
2510 begin
2511 return Check_Calls (N) = Abandon;
2512 end Has_Call_Using_Secondary_Stack;
2514 --------------------
2515 -- Process_Bounds --
2516 --------------------
2518 procedure Process_Bounds (R : Node_Id) is
2519 Loc : constant Source_Ptr := Sloc (N);
2521 function One_Bound
2522 (Original_Bound : Node_Id;
2523 Analyzed_Bound : Node_Id;
2524 Typ : Entity_Id) return Node_Id;
2525 -- Capture value of bound and return captured value
2527 ---------------
2528 -- One_Bound --
2529 ---------------
2531 function One_Bound
2532 (Original_Bound : Node_Id;
2533 Analyzed_Bound : Node_Id;
2534 Typ : Entity_Id) return Node_Id
2536 Assign : Node_Id;
2537 Decl : Node_Id;
2538 Id : Entity_Id;
2540 begin
2541 -- If the bound is a constant or an object, no need for a separate
2542 -- declaration. If the bound is the result of previous expansion
2543 -- it is already analyzed and should not be modified. Note that
2544 -- the Bound will be resolved later, if needed, as part of the
2545 -- call to Make_Index (literal bounds may need to be resolved to
2546 -- type Integer).
2548 if Analyzed (Original_Bound) then
2549 return Original_Bound;
2551 elsif Nkind_In (Analyzed_Bound, N_Integer_Literal,
2552 N_Character_Literal)
2553 or else Is_Entity_Name (Analyzed_Bound)
2554 then
2555 Analyze_And_Resolve (Original_Bound, Typ);
2556 return Original_Bound;
2557 end if;
2559 -- Normally, the best approach is simply to generate a constant
2560 -- declaration that captures the bound. However, there is a nasty
2561 -- case where this is wrong. If the bound is complex, and has a
2562 -- possible use of the secondary stack, we need to generate a
2563 -- separate assignment statement to ensure the creation of a block
2564 -- which will release the secondary stack.
2566 -- We prefer the constant declaration, since it leaves us with a
2567 -- proper trace of the value, useful in optimizations that get rid
2568 -- of junk range checks.
2570 if not Has_Call_Using_Secondary_Stack (Analyzed_Bound) then
2571 Analyze_And_Resolve (Original_Bound, Typ);
2573 -- Ensure that the bound is valid. This check should not be
2574 -- generated when the range belongs to a quantified expression
2575 -- as the construct is still not expanded into its final form.
2577 if Nkind (Parent (R)) /= N_Loop_Parameter_Specification
2578 or else Nkind (Parent (Parent (R))) /= N_Quantified_Expression
2579 then
2580 Ensure_Valid (Original_Bound);
2581 end if;
2583 Force_Evaluation (Original_Bound);
2584 return Original_Bound;
2585 end if;
2587 Id := Make_Temporary (Loc, 'R', Original_Bound);
2589 -- Here we make a declaration with a separate assignment
2590 -- statement, and insert before loop header.
2592 Decl :=
2593 Make_Object_Declaration (Loc,
2594 Defining_Identifier => Id,
2595 Object_Definition => New_Occurrence_Of (Typ, Loc));
2597 Assign :=
2598 Make_Assignment_Statement (Loc,
2599 Name => New_Occurrence_Of (Id, Loc),
2600 Expression => Relocate_Node (Original_Bound));
2602 Insert_Actions (Loop_Nod, New_List (Decl, Assign));
2604 -- Now that this temporary variable is initialized we decorate it
2605 -- as safe-to-reevaluate to inform to the backend that no further
2606 -- asignment will be issued and hence it can be handled as side
2607 -- effect free. Note that this decoration must be done when the
2608 -- assignment has been analyzed because otherwise it will be
2609 -- rejected (see Analyze_Assignment).
2611 Set_Is_Safe_To_Reevaluate (Id);
2613 Rewrite (Original_Bound, New_Occurrence_Of (Id, Loc));
2615 if Nkind (Assign) = N_Assignment_Statement then
2616 return Expression (Assign);
2617 else
2618 return Original_Bound;
2619 end if;
2620 end One_Bound;
2622 Hi : constant Node_Id := High_Bound (R);
2623 Lo : constant Node_Id := Low_Bound (R);
2624 R_Copy : constant Node_Id := New_Copy_Tree (R);
2625 New_Hi : Node_Id;
2626 New_Lo : Node_Id;
2627 Typ : Entity_Id;
2629 -- Start of processing for Process_Bounds
2631 begin
2632 Set_Parent (R_Copy, Parent (R));
2633 Preanalyze_Range (R_Copy);
2634 Typ := Etype (R_Copy);
2636 -- If the type of the discrete range is Universal_Integer, then the
2637 -- bound's type must be resolved to Integer, and any object used to
2638 -- hold the bound must also have type Integer, unless the literal
2639 -- bounds are constant-folded expressions with a user-defined type.
2641 if Typ = Universal_Integer then
2642 if Nkind (Lo) = N_Integer_Literal
2643 and then Present (Etype (Lo))
2644 and then Scope (Etype (Lo)) /= Standard_Standard
2645 then
2646 Typ := Etype (Lo);
2648 elsif Nkind (Hi) = N_Integer_Literal
2649 and then Present (Etype (Hi))
2650 and then Scope (Etype (Hi)) /= Standard_Standard
2651 then
2652 Typ := Etype (Hi);
2654 else
2655 Typ := Standard_Integer;
2656 end if;
2657 end if;
2659 Set_Etype (R, Typ);
2661 New_Lo := One_Bound (Lo, Low_Bound (R_Copy), Typ);
2662 New_Hi := One_Bound (Hi, High_Bound (R_Copy), Typ);
2664 -- Propagate staticness to loop range itself, in case the
2665 -- corresponding subtype is static.
2667 if New_Lo /= Lo and then Is_OK_Static_Expression (New_Lo) then
2668 Rewrite (Low_Bound (R), New_Copy (New_Lo));
2669 end if;
2671 if New_Hi /= Hi and then Is_OK_Static_Expression (New_Hi) then
2672 Rewrite (High_Bound (R), New_Copy (New_Hi));
2673 end if;
2674 end Process_Bounds;
2676 -- Local variables
2678 DS : constant Node_Id := Discrete_Subtype_Definition (N);
2679 Id : constant Entity_Id := Defining_Identifier (N);
2681 DS_Copy : Node_Id;
2683 -- Start of processing for Analyze_Loop_Parameter_Specification
2685 begin
2686 Enter_Name (Id);
2688 -- We always consider the loop variable to be referenced, since the loop
2689 -- may be used just for counting purposes.
2691 Generate_Reference (Id, N, ' ');
2693 -- Check for the case of loop variable hiding a local variable (used
2694 -- later on to give a nice warning if the hidden variable is never
2695 -- assigned).
2697 declare
2698 H : constant Entity_Id := Homonym (Id);
2699 begin
2700 if Present (H)
2701 and then Ekind (H) = E_Variable
2702 and then Is_Discrete_Type (Etype (H))
2703 and then Enclosing_Dynamic_Scope (H) = Enclosing_Dynamic_Scope (Id)
2704 then
2705 Set_Hiding_Loop_Variable (H, Id);
2706 end if;
2707 end;
2709 -- Loop parameter specification must include subtype mark in SPARK
2711 if Nkind (DS) = N_Range then
2712 Check_SPARK_05_Restriction
2713 ("loop parameter specification must include subtype mark", N);
2714 end if;
2716 -- Analyze the subtype definition and create temporaries for the bounds.
2717 -- Do not evaluate the range when preanalyzing a quantified expression
2718 -- because bounds expressed as function calls with side effects will be
2719 -- incorrectly replicated.
2721 if Nkind (DS) = N_Range
2722 and then Expander_Active
2723 and then Nkind (Parent (N)) /= N_Quantified_Expression
2724 then
2725 Process_Bounds (DS);
2727 -- Either the expander not active or the range of iteration is a subtype
2728 -- indication, an entity, or a function call that yields an aggregate or
2729 -- a container.
2731 else
2732 DS_Copy := New_Copy_Tree (DS);
2733 Set_Parent (DS_Copy, Parent (DS));
2734 Preanalyze_Range (DS_Copy);
2736 -- Ada 2012: If the domain of iteration is:
2738 -- a) a function call,
2739 -- b) an identifier that is not a type,
2740 -- c) an attribute reference 'Old (within a postcondition)
2741 -- d) an unchecked conversion
2743 -- then it is an iteration over a container. It was classified as
2744 -- a loop specification by the parser, and must be rewritten now
2745 -- to activate container iteration. The last case will occur within
2746 -- an expanded inlined call, where the expansion wraps an actual in
2747 -- an unchecked conversion when needed. The expression of the
2748 -- conversion is always an object.
2750 if Nkind (DS_Copy) = N_Function_Call
2751 or else (Is_Entity_Name (DS_Copy)
2752 and then not Is_Type (Entity (DS_Copy)))
2753 or else (Nkind (DS_Copy) = N_Attribute_Reference
2754 and then Nam_In (Attribute_Name (DS_Copy),
2755 Name_Old, Name_Loop_Entry))
2756 or else Nkind (DS_Copy) = N_Unchecked_Type_Conversion
2757 or else Has_Aspect (Etype (DS_Copy), Aspect_Iterable)
2758 then
2759 -- This is an iterator specification. Rewrite it as such and
2760 -- analyze it to capture function calls that may require
2761 -- finalization actions.
2763 declare
2764 I_Spec : constant Node_Id :=
2765 Make_Iterator_Specification (Sloc (N),
2766 Defining_Identifier => Relocate_Node (Id),
2767 Name => DS_Copy,
2768 Subtype_Indication => Empty,
2769 Reverse_Present => Reverse_Present (N));
2770 Scheme : constant Node_Id := Parent (N);
2772 begin
2773 Set_Iterator_Specification (Scheme, I_Spec);
2774 Set_Loop_Parameter_Specification (Scheme, Empty);
2775 Analyze_Iterator_Specification (I_Spec);
2777 -- In a generic context, analyze the original domain of
2778 -- iteration, for name capture.
2780 if not Expander_Active then
2781 Analyze (DS);
2782 end if;
2784 -- Set kind of loop parameter, which may be used in the
2785 -- subsequent analysis of the condition in a quantified
2786 -- expression.
2788 Set_Ekind (Id, E_Loop_Parameter);
2789 return;
2790 end;
2792 -- Domain of iteration is not a function call, and is side-effect
2793 -- free.
2795 else
2796 -- A quantified expression that appears in a pre/post condition
2797 -- is pre-analyzed several times. If the range is given by an
2798 -- attribute reference it is rewritten as a range, and this is
2799 -- done even with expansion disabled. If the type is already set
2800 -- do not reanalyze, because a range with static bounds may be
2801 -- typed Integer by default.
2803 if Nkind (Parent (N)) = N_Quantified_Expression
2804 and then Present (Etype (DS))
2805 then
2806 null;
2807 else
2808 Analyze (DS);
2809 end if;
2810 end if;
2811 end if;
2813 if DS = Error then
2814 return;
2815 end if;
2817 -- Some additional checks if we are iterating through a type
2819 if Is_Entity_Name (DS)
2820 and then Present (Entity (DS))
2821 and then Is_Type (Entity (DS))
2822 then
2823 -- The subtype indication may denote the completion of an incomplete
2824 -- type declaration.
2826 if Ekind (Entity (DS)) = E_Incomplete_Type then
2827 Set_Entity (DS, Get_Full_View (Entity (DS)));
2828 Set_Etype (DS, Entity (DS));
2829 end if;
2831 Check_Predicate_Use (Entity (DS));
2832 end if;
2834 -- Error if not discrete type
2836 if not Is_Discrete_Type (Etype (DS)) then
2837 Wrong_Type (DS, Any_Discrete);
2838 Set_Etype (DS, Any_Type);
2839 end if;
2841 Check_Controlled_Array_Attribute (DS);
2843 if Nkind (DS) = N_Subtype_Indication then
2844 Check_Predicate_Use (Entity (Subtype_Mark (DS)));
2845 end if;
2847 Make_Index (DS, N, In_Iter_Schm => True);
2848 Set_Ekind (Id, E_Loop_Parameter);
2850 -- A quantified expression which appears in a pre- or post-condition may
2851 -- be analyzed multiple times. The analysis of the range creates several
2852 -- itypes which reside in different scopes depending on whether the pre-
2853 -- or post-condition has been expanded. Update the type of the loop
2854 -- variable to reflect the proper itype at each stage of analysis.
2856 if No (Etype (Id))
2857 or else Etype (Id) = Any_Type
2858 or else
2859 (Present (Etype (Id))
2860 and then Is_Itype (Etype (Id))
2861 and then Nkind (Parent (Loop_Nod)) = N_Expression_With_Actions
2862 and then Nkind (Original_Node (Parent (Loop_Nod))) =
2863 N_Quantified_Expression)
2864 then
2865 Set_Etype (Id, Etype (DS));
2866 end if;
2868 -- Treat a range as an implicit reference to the type, to inhibit
2869 -- spurious warnings.
2871 Generate_Reference (Base_Type (Etype (DS)), N, ' ');
2872 Set_Is_Known_Valid (Id, True);
2874 -- The loop is not a declarative part, so the loop variable must be
2875 -- frozen explicitly. Do not freeze while preanalyzing a quantified
2876 -- expression because the freeze node will not be inserted into the
2877 -- tree due to flag Is_Spec_Expression being set.
2879 if Nkind (Parent (N)) /= N_Quantified_Expression then
2880 declare
2881 Flist : constant List_Id := Freeze_Entity (Id, N);
2882 begin
2883 if Is_Non_Empty_List (Flist) then
2884 Insert_Actions (N, Flist);
2885 end if;
2886 end;
2887 end if;
2889 -- Case where we have a range or a subtype, get type bounds
2891 if Nkind_In (DS, N_Range, N_Subtype_Indication)
2892 and then not Error_Posted (DS)
2893 and then Etype (DS) /= Any_Type
2894 and then Is_Discrete_Type (Etype (DS))
2895 then
2896 declare
2897 L : Node_Id;
2898 H : Node_Id;
2900 begin
2901 if Nkind (DS) = N_Range then
2902 L := Low_Bound (DS);
2903 H := High_Bound (DS);
2904 else
2905 L :=
2906 Type_Low_Bound (Underlying_Type (Etype (Subtype_Mark (DS))));
2907 H :=
2908 Type_High_Bound (Underlying_Type (Etype (Subtype_Mark (DS))));
2909 end if;
2911 -- Check for null or possibly null range and issue warning. We
2912 -- suppress such messages in generic templates and instances,
2913 -- because in practice they tend to be dubious in these cases. The
2914 -- check applies as well to rewritten array element loops where a
2915 -- null range may be detected statically.
2917 if Compile_Time_Compare (L, H, Assume_Valid => True) = GT then
2919 -- Suppress the warning if inside a generic template or
2920 -- instance, since in practice they tend to be dubious in these
2921 -- cases since they can result from intended parameterization.
2923 if not Inside_A_Generic and then not In_Instance then
2925 -- Specialize msg if invalid values could make the loop
2926 -- non-null after all.
2928 if Compile_Time_Compare
2929 (L, H, Assume_Valid => False) = GT
2930 then
2931 -- Since we know the range of the loop is null, set the
2932 -- appropriate flag to remove the loop entirely during
2933 -- expansion.
2935 Set_Is_Null_Loop (Loop_Nod);
2937 if Comes_From_Source (N) then
2938 Error_Msg_N
2939 ("??loop range is null, loop will not execute", DS);
2940 end if;
2942 -- Here is where the loop could execute because of
2943 -- invalid values, so issue appropriate message and in
2944 -- this case we do not set the Is_Null_Loop flag since
2945 -- the loop may execute.
2947 elsif Comes_From_Source (N) then
2948 Error_Msg_N
2949 ("??loop range may be null, loop may not execute",
2950 DS);
2951 Error_Msg_N
2952 ("??can only execute if invalid values are present",
2953 DS);
2954 end if;
2955 end if;
2957 -- In either case, suppress warnings in the body of the loop,
2958 -- since it is likely that these warnings will be inappropriate
2959 -- if the loop never actually executes, which is likely.
2961 Set_Suppress_Loop_Warnings (Loop_Nod);
2963 -- The other case for a warning is a reverse loop where the
2964 -- upper bound is the integer literal zero or one, and the
2965 -- lower bound may exceed this value.
2967 -- For example, we have
2969 -- for J in reverse N .. 1 loop
2971 -- In practice, this is very likely to be a case of reversing
2972 -- the bounds incorrectly in the range.
2974 elsif Reverse_Present (N)
2975 and then Nkind (Original_Node (H)) = N_Integer_Literal
2976 and then
2977 (Intval (Original_Node (H)) = Uint_0
2978 or else
2979 Intval (Original_Node (H)) = Uint_1)
2980 then
2981 -- Lower bound may in fact be known and known not to exceed
2982 -- upper bound (e.g. reverse 0 .. 1) and that's OK.
2984 if Compile_Time_Known_Value (L)
2985 and then Expr_Value (L) <= Expr_Value (H)
2986 then
2987 null;
2989 -- Otherwise warning is warranted
2991 else
2992 Error_Msg_N ("??loop range may be null", DS);
2993 Error_Msg_N ("\??bounds may be wrong way round", DS);
2994 end if;
2995 end if;
2997 -- Check if either bound is known to be outside the range of the
2998 -- loop parameter type, this is e.g. the case of a loop from
2999 -- 20..X where the type is 1..19.
3001 -- Such a loop is dubious since either it raises CE or it executes
3002 -- zero times, and that cannot be useful!
3004 if Etype (DS) /= Any_Type
3005 and then not Error_Posted (DS)
3006 and then Nkind (DS) = N_Subtype_Indication
3007 and then Nkind (Constraint (DS)) = N_Range_Constraint
3008 then
3009 declare
3010 LLo : constant Node_Id :=
3011 Low_Bound (Range_Expression (Constraint (DS)));
3012 LHi : constant Node_Id :=
3013 High_Bound (Range_Expression (Constraint (DS)));
3015 Bad_Bound : Node_Id := Empty;
3016 -- Suspicious loop bound
3018 begin
3019 -- At this stage L, H are the bounds of the type, and LLo
3020 -- Lhi are the low bound and high bound of the loop.
3022 if Compile_Time_Compare (LLo, L, Assume_Valid => True) = LT
3023 or else
3024 Compile_Time_Compare (LLo, H, Assume_Valid => True) = GT
3025 then
3026 Bad_Bound := LLo;
3027 end if;
3029 if Compile_Time_Compare (LHi, L, Assume_Valid => True) = LT
3030 or else
3031 Compile_Time_Compare (LHi, H, Assume_Valid => True) = GT
3032 then
3033 Bad_Bound := LHi;
3034 end if;
3036 if Present (Bad_Bound) then
3037 Error_Msg_N
3038 ("suspicious loop bound out of range of "
3039 & "loop subtype??", Bad_Bound);
3040 Error_Msg_N
3041 ("\loop executes zero times or raises "
3042 & "Constraint_Error??", Bad_Bound);
3043 end if;
3044 end;
3045 end if;
3047 -- This declare block is about warnings, if we get an exception while
3048 -- testing for warnings, we simply abandon the attempt silently. This
3049 -- most likely occurs as the result of a previous error, but might
3050 -- just be an obscure case we have missed. In either case, not giving
3051 -- the warning is perfectly acceptable.
3053 exception
3054 when others => null;
3055 end;
3056 end if;
3058 -- A loop parameter cannot be effectively volatile (SPARK RM 7.1.3(4)).
3059 -- This check is relevant only when SPARK_Mode is on as it is not a
3060 -- standard Ada legality check.
3062 if SPARK_Mode = On and then Is_Effectively_Volatile (Id) then
3063 Error_Msg_N ("loop parameter cannot be volatile", Id);
3064 end if;
3065 end Analyze_Loop_Parameter_Specification;
3067 ----------------------------
3068 -- Analyze_Loop_Statement --
3069 ----------------------------
3071 procedure Analyze_Loop_Statement (N : Node_Id) is
3073 function Is_Container_Iterator (Iter : Node_Id) return Boolean;
3074 -- Given a loop iteration scheme, determine whether it is an Ada 2012
3075 -- container iteration.
3077 function Is_Wrapped_In_Block (N : Node_Id) return Boolean;
3078 -- Determine whether loop statement N has been wrapped in a block to
3079 -- capture finalization actions that may be generated for container
3080 -- iterators. Prevents infinite recursion when block is analyzed.
3081 -- Routine is a noop if loop is single statement within source block.
3083 ---------------------------
3084 -- Is_Container_Iterator --
3085 ---------------------------
3087 function Is_Container_Iterator (Iter : Node_Id) return Boolean is
3088 begin
3089 -- Infinite loop
3091 if No (Iter) then
3092 return False;
3094 -- While loop
3096 elsif Present (Condition (Iter)) then
3097 return False;
3099 -- for Def_Id in [reverse] Name loop
3100 -- for Def_Id [: Subtype_Indication] of [reverse] Name loop
3102 elsif Present (Iterator_Specification (Iter)) then
3103 declare
3104 Nam : constant Node_Id := Name (Iterator_Specification (Iter));
3105 Nam_Copy : Node_Id;
3107 begin
3108 Nam_Copy := New_Copy_Tree (Nam);
3109 Set_Parent (Nam_Copy, Parent (Nam));
3110 Preanalyze_Range (Nam_Copy);
3112 -- The only two options here are iteration over a container or
3113 -- an array.
3115 return not Is_Array_Type (Etype (Nam_Copy));
3116 end;
3118 -- for Def_Id in [reverse] Discrete_Subtype_Definition loop
3120 else
3121 declare
3122 LP : constant Node_Id := Loop_Parameter_Specification (Iter);
3123 DS : constant Node_Id := Discrete_Subtype_Definition (LP);
3124 DS_Copy : Node_Id;
3126 begin
3127 DS_Copy := New_Copy_Tree (DS);
3128 Set_Parent (DS_Copy, Parent (DS));
3129 Preanalyze_Range (DS_Copy);
3131 -- Check for a call to Iterate ()
3133 return
3134 Nkind (DS_Copy) = N_Function_Call
3135 and then Needs_Finalization (Etype (DS_Copy));
3136 end;
3137 end if;
3138 end Is_Container_Iterator;
3140 -------------------------
3141 -- Is_Wrapped_In_Block --
3142 -------------------------
3144 function Is_Wrapped_In_Block (N : Node_Id) return Boolean is
3145 HSS : Node_Id;
3146 Stat : Node_Id;
3148 begin
3150 -- Check if current scope is a block that is not a transient block.
3152 if Ekind (Current_Scope) /= E_Block
3153 or else No (Block_Node (Current_Scope))
3154 then
3155 return False;
3157 else
3158 HSS :=
3159 Handled_Statement_Sequence (Parent (Block_Node (Current_Scope)));
3161 -- Skip leading pragmas that may be introduced for invariant and
3162 -- predicate checks.
3164 Stat := First (Statements (HSS));
3165 while Present (Stat) and then Nkind (Stat) = N_Pragma loop
3166 Stat := Next (Stat);
3167 end loop;
3169 return Stat = N and then No (Next (Stat));
3170 end if;
3171 end Is_Wrapped_In_Block;
3173 -- Local declarations
3175 Id : constant Node_Id := Identifier (N);
3176 Iter : constant Node_Id := Iteration_Scheme (N);
3177 Loc : constant Source_Ptr := Sloc (N);
3178 Ent : Entity_Id;
3179 Stmt : Node_Id;
3181 -- Start of processing for Analyze_Loop_Statement
3183 begin
3184 if Present (Id) then
3186 -- Make name visible, e.g. for use in exit statements. Loop labels
3187 -- are always considered to be referenced.
3189 Analyze (Id);
3190 Ent := Entity (Id);
3192 -- Guard against serious error (typically, a scope mismatch when
3193 -- semantic analysis is requested) by creating loop entity to
3194 -- continue analysis.
3196 if No (Ent) then
3197 if Total_Errors_Detected /= 0 then
3198 Ent := New_Internal_Entity (E_Loop, Current_Scope, Loc, 'L');
3199 else
3200 raise Program_Error;
3201 end if;
3203 -- Verify that the loop name is hot hidden by an unrelated
3204 -- declaration in an inner scope.
3206 elsif Ekind (Ent) /= E_Label and then Ekind (Ent) /= E_Loop then
3207 Error_Msg_Sloc := Sloc (Ent);
3208 Error_Msg_N ("implicit label declaration for & is hidden#", Id);
3210 if Present (Homonym (Ent))
3211 and then Ekind (Homonym (Ent)) = E_Label
3212 then
3213 Set_Entity (Id, Ent);
3214 Set_Ekind (Ent, E_Loop);
3215 end if;
3217 else
3218 Generate_Reference (Ent, N, ' ');
3219 Generate_Definition (Ent);
3221 -- If we found a label, mark its type. If not, ignore it, since it
3222 -- means we have a conflicting declaration, which would already
3223 -- have been diagnosed at declaration time. Set Label_Construct
3224 -- of the implicit label declaration, which is not created by the
3225 -- parser for generic units.
3227 if Ekind (Ent) = E_Label then
3228 Set_Ekind (Ent, E_Loop);
3230 if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
3231 Set_Label_Construct (Parent (Ent), N);
3232 end if;
3233 end if;
3234 end if;
3236 -- Case of no identifier present. Create one and attach it to the
3237 -- loop statement for use as a scope and as a reference for later
3238 -- expansions. Indicate that the label does not come from source,
3239 -- and attach it to the loop statement so it is part of the tree,
3240 -- even without a full declaration.
3242 else
3243 Ent := New_Internal_Entity (E_Loop, Current_Scope, Loc, 'L');
3244 Set_Etype (Ent, Standard_Void_Type);
3245 Set_Identifier (N, New_Occurrence_Of (Ent, Loc));
3246 Set_Parent (Ent, N);
3247 Set_Has_Created_Identifier (N);
3248 end if;
3250 -- Iteration over a container in Ada 2012 involves the creation of a
3251 -- controlled iterator object. Wrap the loop in a block to ensure the
3252 -- timely finalization of the iterator and release of container locks.
3253 -- The same applies to the use of secondary stack when obtaining an
3254 -- iterator.
3256 if Ada_Version >= Ada_2012
3257 and then Is_Container_Iterator (Iter)
3258 and then not Is_Wrapped_In_Block (N)
3259 then
3260 declare
3261 Block_Nod : Node_Id;
3262 Block_Id : Entity_Id;
3264 begin
3265 Block_Nod :=
3266 Make_Block_Statement (Loc,
3267 Declarations => New_List,
3268 Handled_Statement_Sequence =>
3269 Make_Handled_Sequence_Of_Statements (Loc,
3270 Statements => New_List (Relocate_Node (N))));
3272 Add_Block_Identifier (Block_Nod, Block_Id);
3274 -- The expansion of iterator loops generates an iterator in order
3275 -- to traverse the elements of a container:
3277 -- Iter : <iterator type> := Iterate (Container)'reference;
3279 -- The iterator is controlled and returned on the secondary stack.
3280 -- The analysis of the call to Iterate establishes a transient
3281 -- scope to deal with the secondary stack management, but never
3282 -- really creates a physical block as this would kill the iterator
3283 -- too early (see Wrap_Transient_Declaration). To address this
3284 -- case, mark the generated block as needing secondary stack
3285 -- management.
3287 Set_Uses_Sec_Stack (Block_Id);
3289 Rewrite (N, Block_Nod);
3290 Analyze (N);
3291 return;
3292 end;
3293 end if;
3295 -- Kill current values on entry to loop, since statements in the body of
3296 -- the loop may have been executed before the loop is entered. Similarly
3297 -- we kill values after the loop, since we do not know that the body of
3298 -- the loop was executed.
3300 Kill_Current_Values;
3301 Push_Scope (Ent);
3302 Analyze_Iteration_Scheme (Iter);
3304 -- Check for following case which merits a warning if the type E of is
3305 -- a multi-dimensional array (and no explicit subscript ranges present).
3307 -- for J in E'Range
3308 -- for K in E'Range
3310 if Present (Iter)
3311 and then Present (Loop_Parameter_Specification (Iter))
3312 then
3313 declare
3314 LPS : constant Node_Id := Loop_Parameter_Specification (Iter);
3315 DSD : constant Node_Id :=
3316 Original_Node (Discrete_Subtype_Definition (LPS));
3317 begin
3318 if Nkind (DSD) = N_Attribute_Reference
3319 and then Attribute_Name (DSD) = Name_Range
3320 and then No (Expressions (DSD))
3321 then
3322 declare
3323 Typ : constant Entity_Id := Etype (Prefix (DSD));
3324 begin
3325 if Is_Array_Type (Typ)
3326 and then Number_Dimensions (Typ) > 1
3327 and then Nkind (Parent (N)) = N_Loop_Statement
3328 and then Present (Iteration_Scheme (Parent (N)))
3329 then
3330 declare
3331 OIter : constant Node_Id :=
3332 Iteration_Scheme (Parent (N));
3333 OLPS : constant Node_Id :=
3334 Loop_Parameter_Specification (OIter);
3335 ODSD : constant Node_Id :=
3336 Original_Node (Discrete_Subtype_Definition (OLPS));
3337 begin
3338 if Nkind (ODSD) = N_Attribute_Reference
3339 and then Attribute_Name (ODSD) = Name_Range
3340 and then No (Expressions (ODSD))
3341 and then Etype (Prefix (ODSD)) = Typ
3342 then
3343 Error_Msg_Sloc := Sloc (ODSD);
3344 Error_Msg_N
3345 ("inner range same as outer range#??", DSD);
3346 end if;
3347 end;
3348 end if;
3349 end;
3350 end if;
3351 end;
3352 end if;
3354 -- Analyze the statements of the body except in the case of an Ada 2012
3355 -- iterator with the expander active. In this case the expander will do
3356 -- a rewrite of the loop into a while loop. We will then analyze the
3357 -- loop body when we analyze this while loop.
3359 -- We need to do this delay because if the container is for indefinite
3360 -- types the actual subtype of the components will only be determined
3361 -- when the cursor declaration is analyzed.
3363 -- If the expander is not active then we want to analyze the loop body
3364 -- now even in the Ada 2012 iterator case, since the rewriting will not
3365 -- be done. Insert the loop variable in the current scope, if not done
3366 -- when analysing the iteration scheme. Set its kind properly to detect
3367 -- improper uses in the loop body.
3369 -- In GNATprove mode, we do one of the above depending on the kind of
3370 -- loop. If it is an iterator over an array, then we do not analyze the
3371 -- loop now. We will analyze it after it has been rewritten by the
3372 -- special SPARK expansion which is activated in GNATprove mode. We need
3373 -- to do this so that other expansions that should occur in GNATprove
3374 -- mode take into account the specificities of the rewritten loop, in
3375 -- particular the introduction of a renaming (which needs to be
3376 -- expanded).
3378 -- In other cases in GNATprove mode then we want to analyze the loop
3379 -- body now, since no rewriting will occur.
3381 if Present (Iter)
3382 and then Present (Iterator_Specification (Iter))
3383 then
3384 if GNATprove_Mode
3385 and then Is_Iterator_Over_Array (Iterator_Specification (Iter))
3386 then
3387 null;
3389 elsif not Expander_Active then
3390 declare
3391 I_Spec : constant Node_Id := Iterator_Specification (Iter);
3392 Id : constant Entity_Id := Defining_Identifier (I_Spec);
3394 begin
3395 if Scope (Id) /= Current_Scope then
3396 Enter_Name (Id);
3397 end if;
3399 -- In an element iterator, The loop parameter is a variable if
3400 -- the domain of iteration (container or array) is a variable.
3402 if not Of_Present (I_Spec)
3403 or else not Is_Variable (Name (I_Spec))
3404 then
3405 Set_Ekind (Id, E_Loop_Parameter);
3406 end if;
3407 end;
3409 Analyze_Statements (Statements (N));
3410 end if;
3412 else
3414 -- Pre-Ada2012 for-loops and while loops.
3416 Analyze_Statements (Statements (N));
3417 end if;
3419 -- When the iteration scheme of a loop contains attribute 'Loop_Entry,
3420 -- the loop is transformed into a conditional block. Retrieve the loop.
3422 Stmt := N;
3424 if Subject_To_Loop_Entry_Attributes (Stmt) then
3425 Stmt := Find_Loop_In_Conditional_Block (Stmt);
3426 end if;
3428 -- Finish up processing for the loop. We kill all current values, since
3429 -- in general we don't know if the statements in the loop have been
3430 -- executed. We could do a bit better than this with a loop that we
3431 -- know will execute at least once, but it's not worth the trouble and
3432 -- the front end is not in the business of flow tracing.
3434 Process_End_Label (Stmt, 'e', Ent);
3435 End_Scope;
3436 Kill_Current_Values;
3438 -- Check for infinite loop. Skip check for generated code, since it
3439 -- justs waste time and makes debugging the routine called harder.
3441 -- Note that we have to wait till the body of the loop is fully analyzed
3442 -- before making this call, since Check_Infinite_Loop_Warning relies on
3443 -- being able to use semantic visibility information to find references.
3445 if Comes_From_Source (Stmt) then
3446 Check_Infinite_Loop_Warning (Stmt);
3447 end if;
3449 -- Code after loop is unreachable if the loop has no WHILE or FOR and
3450 -- contains no EXIT statements within the body of the loop.
3452 if No (Iter) and then not Has_Exit (Ent) then
3453 Check_Unreachable_Code (Stmt);
3454 end if;
3455 end Analyze_Loop_Statement;
3457 ----------------------------
3458 -- Analyze_Null_Statement --
3459 ----------------------------
3461 -- Note: the semantics of the null statement is implemented by a single
3462 -- null statement, too bad everything isn't as simple as this.
3464 procedure Analyze_Null_Statement (N : Node_Id) is
3465 pragma Warnings (Off, N);
3466 begin
3467 null;
3468 end Analyze_Null_Statement;
3470 ------------------------
3471 -- Analyze_Statements --
3472 ------------------------
3474 procedure Analyze_Statements (L : List_Id) is
3475 S : Node_Id;
3476 Lab : Entity_Id;
3478 begin
3479 -- The labels declared in the statement list are reachable from
3480 -- statements in the list. We do this as a prepass so that any goto
3481 -- statement will be properly flagged if its target is not reachable.
3482 -- This is not required, but is nice behavior.
3484 S := First (L);
3485 while Present (S) loop
3486 if Nkind (S) = N_Label then
3487 Analyze (Identifier (S));
3488 Lab := Entity (Identifier (S));
3490 -- If we found a label mark it as reachable
3492 if Ekind (Lab) = E_Label then
3493 Generate_Definition (Lab);
3494 Set_Reachable (Lab);
3496 if Nkind (Parent (Lab)) = N_Implicit_Label_Declaration then
3497 Set_Label_Construct (Parent (Lab), S);
3498 end if;
3500 -- If we failed to find a label, it means the implicit declaration
3501 -- of the label was hidden. A for-loop parameter can do this to
3502 -- a label with the same name inside the loop, since the implicit
3503 -- label declaration is in the innermost enclosing body or block
3504 -- statement.
3506 else
3507 Error_Msg_Sloc := Sloc (Lab);
3508 Error_Msg_N
3509 ("implicit label declaration for & is hidden#",
3510 Identifier (S));
3511 end if;
3512 end if;
3514 Next (S);
3515 end loop;
3517 -- Perform semantic analysis on all statements
3519 Conditional_Statements_Begin;
3521 S := First (L);
3522 while Present (S) loop
3523 Analyze (S);
3525 -- Remove dimension in all statements
3527 Remove_Dimension_In_Statement (S);
3528 Next (S);
3529 end loop;
3531 Conditional_Statements_End;
3533 -- Make labels unreachable. Visibility is not sufficient, because labels
3534 -- in one if-branch for example are not reachable from the other branch,
3535 -- even though their declarations are in the enclosing declarative part.
3537 S := First (L);
3538 while Present (S) loop
3539 if Nkind (S) = N_Label then
3540 Set_Reachable (Entity (Identifier (S)), False);
3541 end if;
3543 Next (S);
3544 end loop;
3545 end Analyze_Statements;
3547 ----------------------------
3548 -- Check_Unreachable_Code --
3549 ----------------------------
3551 procedure Check_Unreachable_Code (N : Node_Id) is
3552 Error_Node : Node_Id;
3553 P : Node_Id;
3555 begin
3556 if Is_List_Member (N) and then Comes_From_Source (N) then
3557 declare
3558 Nxt : Node_Id;
3560 begin
3561 Nxt := Original_Node (Next (N));
3563 -- Skip past pragmas
3565 while Nkind (Nxt) = N_Pragma loop
3566 Nxt := Original_Node (Next (Nxt));
3567 end loop;
3569 -- If a label follows us, then we never have dead code, since
3570 -- someone could branch to the label, so we just ignore it, unless
3571 -- we are in formal mode where goto statements are not allowed.
3573 if Nkind (Nxt) = N_Label
3574 and then not Restriction_Check_Required (SPARK_05)
3575 then
3576 return;
3578 -- Otherwise see if we have a real statement following us
3580 elsif Present (Nxt)
3581 and then Comes_From_Source (Nxt)
3582 and then Is_Statement (Nxt)
3583 then
3584 -- Special very annoying exception. If we have a return that
3585 -- follows a raise, then we allow it without a warning, since
3586 -- the Ada RM annoyingly requires a useless return here.
3588 if Nkind (Original_Node (N)) /= N_Raise_Statement
3589 or else Nkind (Nxt) /= N_Simple_Return_Statement
3590 then
3591 -- The rather strange shenanigans with the warning message
3592 -- here reflects the fact that Kill_Dead_Code is very good
3593 -- at removing warnings in deleted code, and this is one
3594 -- warning we would prefer NOT to have removed.
3596 Error_Node := Nxt;
3598 -- If we have unreachable code, analyze and remove the
3599 -- unreachable code, since it is useless and we don't
3600 -- want to generate junk warnings.
3602 -- We skip this step if we are not in code generation mode
3603 -- or CodePeer mode.
3605 -- This is the one case where we remove dead code in the
3606 -- semantics as opposed to the expander, and we do not want
3607 -- to remove code if we are not in code generation mode,
3608 -- since this messes up the ASIS trees or loses useful
3609 -- information in the CodePeer tree.
3611 -- Note that one might react by moving the whole circuit to
3612 -- exp_ch5, but then we lose the warning in -gnatc mode.
3614 if Operating_Mode = Generate_Code
3615 and then not CodePeer_Mode
3616 then
3617 loop
3618 Nxt := Next (N);
3620 -- Quit deleting when we have nothing more to delete
3621 -- or if we hit a label (since someone could transfer
3622 -- control to a label, so we should not delete it).
3624 exit when No (Nxt) or else Nkind (Nxt) = N_Label;
3626 -- Statement/declaration is to be deleted
3628 Analyze (Nxt);
3629 Remove (Nxt);
3630 Kill_Dead_Code (Nxt);
3631 end loop;
3632 end if;
3634 -- Now issue the warning (or error in formal mode)
3636 if Restriction_Check_Required (SPARK_05) then
3637 Check_SPARK_05_Restriction
3638 ("unreachable code is not allowed", Error_Node);
3639 else
3640 Error_Msg ("??unreachable code!", Sloc (Error_Node));
3641 end if;
3642 end if;
3644 -- If the unconditional transfer of control instruction is the
3645 -- last statement of a sequence, then see if our parent is one of
3646 -- the constructs for which we count unblocked exits, and if so,
3647 -- adjust the count.
3649 else
3650 P := Parent (N);
3652 -- Statements in THEN part or ELSE part of IF statement
3654 if Nkind (P) = N_If_Statement then
3655 null;
3657 -- Statements in ELSIF part of an IF statement
3659 elsif Nkind (P) = N_Elsif_Part then
3660 P := Parent (P);
3661 pragma Assert (Nkind (P) = N_If_Statement);
3663 -- Statements in CASE statement alternative
3665 elsif Nkind (P) = N_Case_Statement_Alternative then
3666 P := Parent (P);
3667 pragma Assert (Nkind (P) = N_Case_Statement);
3669 -- Statements in body of block
3671 elsif Nkind (P) = N_Handled_Sequence_Of_Statements
3672 and then Nkind (Parent (P)) = N_Block_Statement
3673 then
3674 -- The original loop is now placed inside a block statement
3675 -- due to the expansion of attribute 'Loop_Entry. Return as
3676 -- this is not a "real" block for the purposes of exit
3677 -- counting.
3679 if Nkind (N) = N_Loop_Statement
3680 and then Subject_To_Loop_Entry_Attributes (N)
3681 then
3682 return;
3683 end if;
3685 -- Statements in exception handler in a block
3687 elsif Nkind (P) = N_Exception_Handler
3688 and then Nkind (Parent (P)) = N_Handled_Sequence_Of_Statements
3689 and then Nkind (Parent (Parent (P))) = N_Block_Statement
3690 then
3691 null;
3693 -- None of these cases, so return
3695 else
3696 return;
3697 end if;
3699 -- This was one of the cases we are looking for (i.e. the
3700 -- parent construct was IF, CASE or block) so decrement count.
3702 Unblocked_Exit_Count := Unblocked_Exit_Count - 1;
3703 end if;
3704 end;
3705 end if;
3706 end Check_Unreachable_Code;
3708 ----------------------
3709 -- Preanalyze_Range --
3710 ----------------------
3712 procedure Preanalyze_Range (R_Copy : Node_Id) is
3713 Save_Analysis : constant Boolean := Full_Analysis;
3714 Typ : Entity_Id;
3716 begin
3717 Full_Analysis := False;
3718 Expander_Mode_Save_And_Set (False);
3720 Analyze (R_Copy);
3722 if Nkind (R_Copy) in N_Subexpr and then Is_Overloaded (R_Copy) then
3724 -- Apply preference rules for range of predefined integer types, or
3725 -- diagnose true ambiguity.
3727 declare
3728 I : Interp_Index;
3729 It : Interp;
3730 Found : Entity_Id := Empty;
3732 begin
3733 Get_First_Interp (R_Copy, I, It);
3734 while Present (It.Typ) loop
3735 if Is_Discrete_Type (It.Typ) then
3736 if No (Found) then
3737 Found := It.Typ;
3738 else
3739 if Scope (Found) = Standard_Standard then
3740 null;
3742 elsif Scope (It.Typ) = Standard_Standard then
3743 Found := It.Typ;
3745 else
3746 -- Both of them are user-defined
3748 Error_Msg_N
3749 ("ambiguous bounds in range of iteration", R_Copy);
3750 Error_Msg_N ("\possible interpretations:", R_Copy);
3751 Error_Msg_NE ("\\} ", R_Copy, Found);
3752 Error_Msg_NE ("\\} ", R_Copy, It.Typ);
3753 exit;
3754 end if;
3755 end if;
3756 end if;
3758 Get_Next_Interp (I, It);
3759 end loop;
3760 end;
3761 end if;
3763 -- Subtype mark in iteration scheme
3765 if Is_Entity_Name (R_Copy) and then Is_Type (Entity (R_Copy)) then
3766 null;
3768 -- Expression in range, or Ada 2012 iterator
3770 elsif Nkind (R_Copy) in N_Subexpr then
3771 Resolve (R_Copy);
3772 Typ := Etype (R_Copy);
3774 if Is_Discrete_Type (Typ) then
3775 null;
3777 -- Check that the resulting object is an iterable container
3779 elsif Has_Aspect (Typ, Aspect_Iterator_Element)
3780 or else Has_Aspect (Typ, Aspect_Constant_Indexing)
3781 or else Has_Aspect (Typ, Aspect_Variable_Indexing)
3782 then
3783 null;
3785 -- The expression may yield an implicit reference to an iterable
3786 -- container. Insert explicit dereference so that proper type is
3787 -- visible in the loop.
3789 elsif Has_Implicit_Dereference (Etype (R_Copy)) then
3790 declare
3791 Disc : Entity_Id;
3793 begin
3794 Disc := First_Discriminant (Typ);
3795 while Present (Disc) loop
3796 if Has_Implicit_Dereference (Disc) then
3797 Build_Explicit_Dereference (R_Copy, Disc);
3798 exit;
3799 end if;
3801 Next_Discriminant (Disc);
3802 end loop;
3803 end;
3805 end if;
3806 end if;
3808 Expander_Mode_Restore;
3809 Full_Analysis := Save_Analysis;
3810 end Preanalyze_Range;
3812 end Sem_Ch5;