i386: Allow all register_operand SUBREGs in x86_ternlog_idx.
[official-gcc.git] / gcc / ada / sem_ch5.adb
blobb92ceb17b1baa619579743159baed4785cf1b6b9
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-2024, 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 Debug; use Debug;
30 with Einfo; use Einfo;
31 with Einfo.Entities; use Einfo.Entities;
32 with Einfo.Utils; use Einfo.Utils;
33 with Errout; use Errout;
34 with Expander; use Expander;
35 with Exp_Ch6; use Exp_Ch6;
36 with Exp_Tss; use Exp_Tss;
37 with Exp_Util; use Exp_Util;
38 with Freeze; use Freeze;
39 with Ghost; use Ghost;
40 with Lib; use Lib;
41 with Lib.Xref; use Lib.Xref;
42 with Mutably_Tagged; use Mutably_Tagged;
43 with Namet; use Namet;
44 with Nlists; use Nlists;
45 with Nmake; use Nmake;
46 with Opt; use Opt;
47 with Sem; use Sem;
48 with Sem_Aux; use Sem_Aux;
49 with Sem_Case; use Sem_Case;
50 with Sem_Ch3; use Sem_Ch3;
51 with Sem_Ch6; use Sem_Ch6;
52 with Sem_Ch8; use Sem_Ch8;
53 with Sem_Dim; use Sem_Dim;
54 with Sem_Disp; use Sem_Disp;
55 with Sem_Elab; use Sem_Elab;
56 with Sem_Eval; use Sem_Eval;
57 with Sem_Res; use Sem_Res;
58 with Sem_Type; use Sem_Type;
59 with Sem_Util; use Sem_Util;
60 with Sem_Warn; use Sem_Warn;
61 with Snames; use Snames;
62 with Stand; use Stand;
63 with Sinfo; use Sinfo;
64 with Sinfo.Nodes; use Sinfo.Nodes;
65 with Sinfo.Utils; use Sinfo.Utils;
66 with Targparm; use Targparm;
67 with Tbuild; use Tbuild;
68 with Ttypes; use Ttypes;
69 with Uintp; use Uintp;
70 with Warnsw; use Warnsw;
72 package body Sem_Ch5 is
74 Current_Assignment : Node_Id := Empty;
75 -- This variable holds the node for an assignment that contains target
76 -- names. The corresponding flag has been set by the parser, and when
77 -- set the analysis of the RHS must be done with all expansion disabled,
78 -- because the assignment is reanalyzed after expansion has replaced all
79 -- occurrences of the target name appropriately.
81 Unblocked_Exit_Count : Nat := 0;
82 -- This variable is used when processing if statements, case statements,
83 -- and block statements. It counts the number of exit points that are not
84 -- blocked by unconditional transfer instructions: for IF and CASE, these
85 -- are the branches of the conditional; for a block, they are the statement
86 -- sequence of the block, and the statement sequences of any exception
87 -- handlers that are part of the block. When processing is complete, if
88 -- this count is zero, it means that control cannot fall through the IF,
89 -- CASE or block statement. This is used for the generation of warning
90 -- messages. This variable is recursively saved on entry to processing the
91 -- construct, and restored on exit.
93 function Has_Sec_Stack_Call (N : Node_Id) return Boolean;
94 -- N is the node for an arbitrary construct. This function searches the
95 -- construct N to see if it contains a function call that returns on the
96 -- secondary stack, returning True if any such call is found, and False
97 -- otherwise.
99 -- ??? The implementation invokes Sem_Util.Requires_Transient_Scope so it
100 -- will return True if N contains a function call that needs finalization,
101 -- in addition to the above specification. See Analyze_Loop_Statement for
102 -- a similar comment about this entanglement.
104 procedure Preanalyze_Range (R_Copy : Node_Id);
105 -- Determine expected type of range or domain of iteration of Ada 2012
106 -- loop by analyzing separate copy. Do the analysis and resolution of the
107 -- copy of the bound(s) with expansion disabled, to prevent the generation
108 -- of finalization actions. This prevents memory leaks when the bounds
109 -- contain calls to functions returning controlled arrays or when the
110 -- domain of iteration is a container.
112 ------------------------
113 -- Analyze_Assignment --
114 ------------------------
116 -- WARNING: This routine manages Ghost regions. Return statements must be
117 -- replaced by gotos which jump to the end of the routine and restore the
118 -- Ghost mode.
120 procedure Analyze_Assignment (N : Node_Id) is
121 Lhs : constant Node_Id := Name (N);
122 Rhs : constant Node_Id := Expression (N);
124 procedure Diagnose_Non_Variable_Lhs (N : Node_Id);
125 -- N is the node for the left hand side of an assignment, and it is not
126 -- a variable. This routine issues an appropriate diagnostic.
128 function Is_Protected_Part_Of_Constituent
129 (Nod : Node_Id) return Boolean;
130 -- Determine whether arbitrary node Nod denotes a Part_Of constituent of
131 -- a single protected type.
133 procedure Kill_Lhs;
134 -- This is called to kill current value settings of a simple variable
135 -- on the left hand side. We call it if we find any error in analyzing
136 -- the assignment, and at the end of processing before setting any new
137 -- current values in place.
139 procedure Set_Assignment_Type
140 (Opnd : Node_Id;
141 Opnd_Type : in out Entity_Id);
142 -- Opnd is either the Lhs or Rhs of the assignment, and Opnd_Type is the
143 -- nominal subtype. This procedure is used to deal with cases where the
144 -- nominal subtype must be replaced by the actual subtype.
146 function Within_Function return Boolean;
147 -- Determine whether the current scope is a function or appears within
148 -- one.
150 -------------------------------
151 -- Diagnose_Non_Variable_Lhs --
152 -------------------------------
154 procedure Diagnose_Non_Variable_Lhs (N : Node_Id) is
155 begin
156 -- Not worth posting another error if left hand side already flagged
157 -- as being illegal in some respect.
159 if Error_Posted (N) then
160 return;
162 -- Some special bad cases of entity names
164 elsif Is_Entity_Name (N) then
165 declare
166 Ent : constant Entity_Id := Entity (N);
168 begin
169 if Ekind (Ent) = E_Loop_Parameter
170 or else Is_Loop_Parameter (Ent)
171 then
172 Error_Msg_N ("assignment to loop parameter not allowed", N);
173 return;
175 elsif Ekind (Ent) = E_In_Parameter then
176 Error_Msg_N
177 ("assignment to IN mode parameter not allowed", N);
178 return;
180 -- Renamings of protected private components are turned into
181 -- constants when compiling a protected function. In the case
182 -- of single protected types, the private component appears
183 -- directly.
185 elsif (Is_Prival (Ent) and then Within_Function)
186 or else Is_Protected_Component (Ent)
187 then
188 Error_Msg_N
189 ("protected function cannot modify its protected object",
191 return;
192 end if;
193 end;
195 -- For indexed components, test prefix if it is in array. We do not
196 -- want to recurse for cases where the prefix is a pointer, since we
197 -- may get a message confusing the pointer and what it references.
199 elsif Nkind (N) = N_Indexed_Component
200 and then Is_Array_Type (Etype (Prefix (N)))
201 then
202 Diagnose_Non_Variable_Lhs (Prefix (N));
203 return;
205 -- Another special case for assignment to discriminant
207 elsif Nkind (N) = N_Selected_Component then
208 if Present (Entity (Selector_Name (N)))
209 and then Ekind (Entity (Selector_Name (N))) = E_Discriminant
210 then
211 Error_Msg_N ("assignment to discriminant not allowed", N);
212 return;
214 -- For selection from record, diagnose prefix, but note that again
215 -- we only do this for a record, not e.g. for a pointer.
217 elsif Is_Record_Type (Etype (Prefix (N))) then
218 Diagnose_Non_Variable_Lhs (Prefix (N));
219 return;
220 end if;
221 end if;
223 -- If we fall through, we have no special message to issue
225 Error_Msg_N ("left hand side of assignment must be a variable", N);
226 end Diagnose_Non_Variable_Lhs;
228 --------------------------------------
229 -- Is_Protected_Part_Of_Constituent --
230 --------------------------------------
232 function Is_Protected_Part_Of_Constituent
233 (Nod : Node_Id) return Boolean
235 Encap_Id : Entity_Id;
236 Var_Id : Entity_Id;
238 begin
239 -- Abstract states and variables may act as Part_Of constituents of
240 -- single protected types, however only variables can be modified by
241 -- an assignment.
243 if Is_Entity_Name (Nod) then
244 Var_Id := Entity (Nod);
246 if Present (Var_Id) and then Ekind (Var_Id) = E_Variable then
247 Encap_Id := Encapsulating_State (Var_Id);
249 -- To qualify, the node must denote a reference to a variable
250 -- whose encapsulating state is a single protected object.
252 return
253 Present (Encap_Id)
254 and then Is_Single_Protected_Object (Encap_Id);
255 end if;
256 end if;
258 return False;
259 end Is_Protected_Part_Of_Constituent;
261 --------------
262 -- Kill_Lhs --
263 --------------
265 procedure Kill_Lhs is
266 begin
267 if Is_Entity_Name (Lhs) then
268 declare
269 Ent : constant Entity_Id := Entity (Lhs);
270 begin
271 if Present (Ent) then
272 Kill_Current_Values (Ent);
273 end if;
274 end;
275 end if;
276 end Kill_Lhs;
278 -------------------------
279 -- Set_Assignment_Type --
280 -------------------------
282 procedure Set_Assignment_Type
283 (Opnd : Node_Id;
284 Opnd_Type : in out Entity_Id)
286 Decl : Node_Id;
288 begin
289 Require_Entity (Opnd);
291 -- If the assignment operand is an in-out or out parameter, then we
292 -- get the actual subtype (needed for the unconstrained case). If the
293 -- operand is the actual in an entry declaration, then within the
294 -- accept statement it is replaced with a local renaming, which may
295 -- also have an actual subtype. Likewise for a return object that
296 -- lives on the secondary stack.
298 if Is_Entity_Name (Opnd)
299 and then (Ekind (Entity (Opnd)) in E_Out_Parameter
300 | E_In_Out_Parameter
301 | E_Generic_In_Out_Parameter
302 or else
303 (Ekind (Entity (Opnd)) = E_Variable
304 and then Nkind (Parent (Entity (Opnd))) =
305 N_Object_Renaming_Declaration
306 and then Nkind (Parent (Parent (Entity (Opnd)))) =
307 N_Accept_Statement)
308 or else Is_Secondary_Stack_Return_Object (Entity (Opnd)))
309 then
310 Opnd_Type := Get_Actual_Subtype (Opnd);
312 -- If the assignment operand is a component reference, then we build
313 -- the actual subtype of the component for the unconstrained case,
314 -- unless there is already one or the type is an unchecked union.
316 elsif (Nkind (Opnd) = N_Selected_Component
317 or else (Nkind (Opnd) = N_Explicit_Dereference
318 and then No (Actual_Designated_Subtype (Opnd))))
319 and then not Is_Unchecked_Union (Opnd_Type)
320 then
321 Decl := Build_Actual_Subtype_Of_Component (Opnd_Type, Opnd);
323 if Present (Decl) then
324 Insert_Action (N, Decl);
325 Mark_Rewrite_Insertion (Decl);
326 Analyze (Decl);
327 Opnd_Type := Defining_Identifier (Decl);
328 Set_Etype (Opnd, Opnd_Type);
329 Freeze_Itype (Opnd_Type, N);
331 elsif Is_Constrained (Etype (Opnd)) then
332 Opnd_Type := Etype (Opnd);
333 end if;
335 -- For slice, use the constrained subtype created for the slice
337 elsif Nkind (Opnd) = N_Slice then
338 Opnd_Type := Etype (Opnd);
339 end if;
340 end Set_Assignment_Type;
342 ---------------------
343 -- Within_Function --
344 ---------------------
346 function Within_Function return Boolean is
347 Scop_Id : constant Entity_Id := Current_Scope;
349 begin
350 if Ekind (Scop_Id) = E_Function then
351 return True;
353 elsif Ekind (Enclosing_Dynamic_Scope (Scop_Id)) = E_Function then
354 return True;
355 end if;
357 return False;
358 end Within_Function;
360 -- Local variables
362 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
363 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
364 -- Save the Ghost-related attributes to restore on exit
366 T1 : Entity_Id;
367 T2 : Entity_Id;
369 Save_Full_Analysis : Boolean := False;
370 -- Force initialization to facilitate static analysis
372 -- Start of processing for Analyze_Assignment
374 begin
375 Mark_Coextensions (N, Rhs);
377 -- Preserve relevant elaboration-related attributes of the context which
378 -- are no longer available or very expensive to recompute once analysis,
379 -- resolution, and expansion are over.
381 Mark_Elaboration_Attributes
382 (N_Id => N,
383 Checks => True,
384 Modes => True);
386 -- An assignment statement is Ghost when the left hand side denotes a
387 -- Ghost entity. Set the mode now to ensure that any nodes generated
388 -- during analysis and expansion are properly marked as Ghost.
390 Mark_And_Set_Ghost_Assignment (N);
392 if Has_Target_Names (N) then
393 pragma Assert (No (Current_Assignment));
394 Current_Assignment := N;
395 Expander_Mode_Save_And_Set (False);
396 Save_Full_Analysis := Full_Analysis;
397 Full_Analysis := False;
398 end if;
400 Analyze (Lhs);
401 Analyze (Rhs);
403 -- Ensure that we never do an assignment on a variable marked as
404 -- Is_Safe_To_Reevaluate.
406 pragma Assert
407 (not Is_Entity_Name (Lhs)
408 or else Ekind (Entity (Lhs)) /= E_Variable
409 or else not Is_Safe_To_Reevaluate (Entity (Lhs)));
411 -- Start type analysis for assignment
413 T1 := Etype (Lhs);
415 -- In the most general case, both Lhs and Rhs can be overloaded, and we
416 -- must compute the intersection of the possible types on each side.
418 if Is_Overloaded (Lhs) then
419 declare
420 I : Interp_Index;
421 It : Interp;
423 begin
424 T1 := Any_Type;
425 Get_First_Interp (Lhs, I, It);
427 while Present (It.Typ) loop
429 -- An indexed component with generalized indexing is always
430 -- overloaded with the corresponding dereference. Discard the
431 -- interpretation that yields a reference type, which is not
432 -- assignable.
434 if Nkind (Lhs) = N_Indexed_Component
435 and then Present (Generalized_Indexing (Lhs))
436 and then Has_Implicit_Dereference (It.Typ)
437 then
438 null;
440 -- This may be a call to a parameterless function through an
441 -- implicit dereference, so discard interpretation as well.
443 elsif Is_Entity_Name (Lhs)
444 and then Has_Implicit_Dereference (It.Typ)
445 then
446 null;
448 elsif Has_Compatible_Type (Rhs, It.Typ) then
449 if T1 = Any_Type then
450 T1 := It.Typ;
451 else
452 -- An explicit dereference is overloaded if the prefix
453 -- is. Try to remove the ambiguity on the prefix, the
454 -- error will be posted there if the ambiguity is real.
456 if Nkind (Lhs) = N_Explicit_Dereference then
457 declare
458 PI : Interp_Index;
459 PI1 : Interp_Index := 0;
460 PIt : Interp;
461 Found : Boolean;
463 begin
464 Found := False;
465 Get_First_Interp (Prefix (Lhs), PI, PIt);
467 while Present (PIt.Typ) loop
468 if Is_Access_Type (PIt.Typ)
469 and then Has_Compatible_Type
470 (Rhs, Designated_Type (PIt.Typ))
471 then
472 if Found then
473 PIt :=
474 Disambiguate (Prefix (Lhs),
475 PI1, PI, Any_Type);
477 if PIt = No_Interp then
478 Error_Msg_N
479 ("ambiguous left-hand side in "
480 & "assignment", Lhs);
481 exit;
482 else
483 Resolve (Prefix (Lhs), PIt.Typ);
484 end if;
486 exit;
487 else
488 Found := True;
489 PI1 := PI;
490 end if;
491 end if;
493 Get_Next_Interp (PI, PIt);
494 end loop;
495 end;
497 else
498 Error_Msg_N
499 ("ambiguous left-hand side in assignment", Lhs);
500 exit;
501 end if;
502 end if;
503 end if;
505 Get_Next_Interp (I, It);
506 end loop;
507 end;
509 if T1 = Any_Type then
510 Error_Msg_N
511 ("no valid types for left-hand side for assignment", Lhs);
512 Kill_Lhs;
513 goto Leave;
514 end if;
515 end if;
517 -- The resulting assignment type is T1, so now we will resolve the left
518 -- hand side of the assignment using this determined type.
520 Resolve (Lhs, T1);
522 -- Cases where Lhs is not a variable. In an instance or an inlined body
523 -- no need for further check because assignment was legal in template.
525 if In_Inlined_Body then
526 null;
528 elsif not Is_Variable (Lhs) then
530 -- Ada 2005 (AI-327): Check assignment to the attribute Priority of a
531 -- protected object.
533 declare
534 Ent : Entity_Id;
535 S : Entity_Id;
537 begin
538 if Ada_Version >= Ada_2005 then
540 -- Handle chains of renamings
542 Ent := Lhs;
543 while Nkind (Ent) in N_Has_Entity
544 and then Present (Entity (Ent))
545 and then Is_Object (Entity (Ent))
546 and then Present (Renamed_Object (Entity (Ent)))
547 loop
548 Ent := Renamed_Object (Entity (Ent));
549 end loop;
551 if (Nkind (Ent) = N_Attribute_Reference
552 and then Attribute_Name (Ent) = Name_Priority)
554 -- Renamings of the attribute Priority applied to protected
555 -- objects have been previously expanded into calls to the
556 -- Get_Ceiling run-time subprogram.
558 or else Is_Expanded_Priority_Attribute (Ent)
559 then
560 -- The enclosing subprogram cannot be a protected function
562 S := Current_Scope;
563 while not (Is_Subprogram (S)
564 and then Convention (S) = Convention_Protected)
565 and then S /= Standard_Standard
566 loop
567 S := Scope (S);
568 end loop;
570 if Ekind (S) = E_Function
571 and then Convention (S) = Convention_Protected
572 then
573 Error_Msg_N
574 ("protected function cannot modify its protected " &
575 "object",
576 Lhs);
577 end if;
579 -- Changes of the ceiling priority of the protected object
580 -- are only effective if the Ceiling_Locking policy is in
581 -- effect (AARM D.5.2 (5/2)).
583 if Locking_Policy /= 'C' then
584 Error_Msg_N
585 ("assignment to the attribute PRIORITY has no effect??",
586 Lhs);
587 Error_Msg_N
588 ("\since no Locking_Policy has been specified??", Lhs);
589 end if;
591 goto Leave;
592 end if;
593 end if;
594 end;
596 Diagnose_Non_Variable_Lhs (Lhs);
597 goto Leave;
599 -- Error of assigning to limited type. We do however allow this in
600 -- certain cases where the front end generates the assignments.
601 -- Comes_From_Source test is needed to allow compiler-generated
602 -- streaming/put_image subprograms, which may ignore privacy.
604 elsif Is_Limited_Type (T1)
605 and then not Assignment_OK (Lhs)
606 and then not Assignment_OK (Original_Node (Lhs))
607 and then (Comes_From_Source (N) or Is_Immutably_Limited_Type (T1))
608 then
609 -- CPP constructors can only be called in declarations
611 if Is_CPP_Constructor_Call (Rhs) then
612 Error_Msg_N ("invalid use of 'C'P'P constructor", Rhs);
613 else
614 Error_Msg_N
615 ("left hand of assignment must not be limited type", Lhs);
616 Explain_Limited_Type (T1, Lhs);
617 end if;
619 goto Leave;
621 -- A class-wide type may be a limited view. This illegal case is not
622 -- caught by previous checks.
624 elsif Ekind (T1) = E_Class_Wide_Type and then From_Limited_With (T1) then
625 Error_Msg_NE ("invalid use of limited view of&", Lhs, T1);
626 goto Leave;
628 -- Enforce RM 3.9.3 (8): the target of an assignment operation cannot be
629 -- abstract. This is only checked when the assignment Comes_From_Source,
630 -- because in some cases the expander generates such assignments (such
631 -- in the _assign operation for an abstract type).
633 elsif Is_Abstract_Type (T1) and then Comes_From_Source (N) then
634 Error_Msg_N
635 ("target of assignment operation must not be abstract", Lhs);
636 end if;
638 -- Variables which are Part_Of constituents of single protected types
639 -- behave in similar fashion to protected components. Such variables
640 -- cannot be modified by protected functions.
642 if Is_Protected_Part_Of_Constituent (Lhs) and then Within_Function then
643 Error_Msg_N
644 ("protected function cannot modify its protected object", Lhs);
645 end if;
647 -- Resolution may have updated the subtype, in case the left-hand side
648 -- is a private protected component. Use the correct subtype to avoid
649 -- scoping issues in the back-end.
651 T1 := Etype (Lhs);
653 -- Ada 2005 (AI-50217, AI-326): Check wrong dereference of incomplete
654 -- type. For example:
656 -- limited with P;
657 -- package Pkg is
658 -- type Acc is access P.T;
659 -- end Pkg;
661 -- with Pkg; use Acc;
662 -- procedure Example is
663 -- A, B : Acc;
664 -- begin
665 -- A.all := B.all; -- ERROR
666 -- end Example;
668 if Nkind (Lhs) = N_Explicit_Dereference
669 and then Ekind (T1) = E_Incomplete_Type
670 then
671 Error_Msg_N ("invalid use of incomplete type", Lhs);
672 Kill_Lhs;
673 goto Leave;
674 end if;
676 -- Now we can complete the resolution of the right hand side
678 Set_Assignment_Type (Lhs, T1);
680 -- When analyzing a mutably tagged class-wide equivalent type pretend we
681 -- are actually looking at the mutably tagged type itself for proper
682 -- analysis.
684 T1 := Get_Corresponding_Mutably_Tagged_Type_If_Present (T1);
686 -- If the target of the assignment is an entity of a mutably tagged type
687 -- and the expression is a conditional expression, its alternatives can
688 -- be of different subtypes of the nominal type of the LHS, so they must
689 -- be resolved with the base type, given that their subtype may differ
690 -- from that of the target mutable object.
692 if Is_Entity_Name (Lhs)
693 and then Is_Assignable (Entity (Lhs))
694 and then Is_Composite_Type (T1)
695 and then not Is_Constrained (Etype (Entity (Lhs)))
696 and then Nkind (Rhs) in N_If_Expression | N_Case_Expression
697 then
698 Resolve (Rhs, Base_Type (T1));
700 else
701 Resolve (Rhs, T1);
702 end if;
704 -- This is the point at which we check for an unset reference
706 Check_Unset_Reference (Rhs);
707 Check_Unprotected_Access (Lhs, Rhs);
709 -- Remaining steps are skipped if Rhs was syntactically in error
711 if Rhs = Error then
712 Kill_Lhs;
713 goto Leave;
714 end if;
716 T2 := Etype (Rhs);
718 if not Covers (T1, T2) then
719 Wrong_Type (Rhs, Etype (Lhs));
720 Kill_Lhs;
721 goto Leave;
722 end if;
724 -- Ada 2005 (AI-326): In case of explicit dereference of incomplete
725 -- types, use the non-limited view if available
727 if Nkind (Rhs) = N_Explicit_Dereference
728 and then Is_Tagged_Type (T2)
729 and then Has_Non_Limited_View (T2)
730 then
731 T2 := Non_Limited_View (T2);
732 end if;
734 Set_Assignment_Type (Rhs, T2);
736 if Total_Errors_Detected /= 0 then
737 if No (T1) then
738 T1 := Any_Type;
739 end if;
741 if No (T2) then
742 T2 := Any_Type;
743 end if;
744 end if;
746 if T1 = Any_Type or else T2 = Any_Type then
747 Kill_Lhs;
748 goto Leave;
749 end if;
751 -- If the rhs is class-wide or dynamically tagged, then require the lhs
752 -- to be class-wide. The case where the rhs is a dynamically tagged call
753 -- to a dispatching operation with a controlling access result is
754 -- excluded from this check, since the target has an access type (and
755 -- no tag propagation occurs in that case).
757 if (Is_Class_Wide_Type (T2)
758 or else (Is_Dynamically_Tagged (Rhs)
759 and then not Is_Access_Type (T1)))
760 and then not Is_Class_Wide_Type (T1)
761 then
762 Error_Msg_N ("dynamically tagged expression not allowed!", Rhs);
764 elsif Is_Class_Wide_Type (T1)
765 and then not Is_Class_Wide_Type (T2)
766 and then not Is_Tag_Indeterminate (Rhs)
767 and then not Is_Dynamically_Tagged (Rhs)
768 then
769 Error_Msg_N ("dynamically tagged expression required!", Rhs);
770 end if;
772 -- Propagate the tag from a class-wide target to the rhs when the rhs
773 -- is a tag-indeterminate call.
775 if Is_Tag_Indeterminate (Rhs) then
776 if Is_Class_Wide_Type (T1) then
777 Propagate_Tag (Lhs, Rhs);
779 elsif Nkind (Rhs) = N_Function_Call
780 and then Is_Entity_Name (Name (Rhs))
781 and then Is_Abstract_Subprogram (Entity (Name (Rhs)))
782 then
783 Error_Msg_N
784 ("call to abstract function must be dispatching", Name (Rhs));
786 elsif Nkind (Rhs) = N_Qualified_Expression
787 and then Nkind (Expression (Rhs)) = N_Function_Call
788 and then Is_Entity_Name (Name (Expression (Rhs)))
789 and then
790 Is_Abstract_Subprogram (Entity (Name (Expression (Rhs))))
791 then
792 Error_Msg_N
793 ("call to abstract function must be dispatching",
794 Name (Expression (Rhs)));
795 end if;
796 end if;
798 -- Ada 2005 (AI-385): When the lhs type is an anonymous access type,
799 -- apply an implicit conversion of the rhs to that type to force
800 -- appropriate static and run-time accessibility checks. This applies
801 -- as well to anonymous access-to-subprogram types that are component
802 -- subtypes or formal parameters.
804 if Ada_Version >= Ada_2005 and then Is_Access_Type (T1) then
805 if Is_Local_Anonymous_Access (T1)
806 or else Ekind (T2) = E_Anonymous_Access_Subprogram_Type
808 -- Handle assignment to an Ada 2012 stand-alone object
809 -- of an anonymous access type.
811 or else (Ekind (T1) = E_Anonymous_Access_Type
812 and then Nkind (Associated_Node_For_Itype (T1)) =
813 N_Object_Declaration)
815 then
816 Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
817 Analyze_And_Resolve (Rhs, T1);
818 end if;
819 end if;
821 -- Ada 2005 (AI-231): Assignment to not null variable
823 if Ada_Version >= Ada_2005
824 and then Can_Never_Be_Null (T1)
825 and then not Assignment_OK (Lhs)
826 then
827 -- Case where we know the right hand side is null
829 if Known_Null (Rhs) then
830 Apply_Compile_Time_Constraint_Error
831 (N => Rhs,
832 Msg =>
833 "(Ada 2005) NULL not allowed in null-excluding objects??",
834 Reason => CE_Null_Not_Allowed);
836 -- We still mark this as a possible modification, that's necessary
837 -- to reset Is_True_Constant, and desirable for xref purposes.
839 Note_Possible_Modification (Lhs, Sure => True);
840 goto Leave;
842 -- If we know the right hand side is non-null, then we convert to the
843 -- target type, since we don't need a run time check in that case.
845 elsif not Can_Never_Be_Null (T2) then
846 Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
847 Analyze_And_Resolve (Rhs, T1);
848 end if;
849 end if;
851 if Is_Scalar_Type (T1) then
852 declare
854 function Omit_Range_Check_For_Streaming return Boolean;
855 -- Return True if this assignment statement is the expansion of
856 -- a Some_Scalar_Type'Read procedure call such that all conditions
857 -- of 13.3.2(35)'s "no check is made" rule are met.
859 ------------------------------------
860 -- Omit_Range_Check_For_Streaming --
861 ------------------------------------
863 function Omit_Range_Check_For_Streaming return Boolean is
864 begin
865 -- Have we got an implicitly generated assignment to a
866 -- component of a composite object? If not, return False.
868 if Comes_From_Source (N)
869 or else Serious_Errors_Detected > 0
870 or else Nkind (Lhs)
871 not in N_Selected_Component | N_Indexed_Component
872 then
873 return False;
874 end if;
876 declare
877 Pref : constant Node_Id := Prefix (Lhs);
878 begin
879 -- Are we in the implicitly-defined Read subprogram
880 -- for a composite type, reading the value of a scalar
881 -- component from the stream? If not, return False.
883 if Nkind (Pref) /= N_Identifier
884 or else not Is_TSS (Scope (Entity (Pref)), TSS_Stream_Read)
885 then
886 return False;
887 end if;
889 -- Return False if Default_Value or Default_Component_Value
890 -- aspect applies.
892 if Has_Default_Aspect (Etype (Lhs))
893 or else Has_Default_Aspect (Etype (Pref))
894 then
895 return False;
897 -- Are we assigning to a record component (as opposed to
898 -- an array component)?
900 elsif Nkind (Lhs) = N_Selected_Component then
902 -- Are we assigning to a nondiscriminant component
903 -- that lacks a default initial value expression?
904 -- If so, return True.
906 declare
907 Comp_Id : constant Entity_Id :=
908 Original_Record_Component
909 (Entity (Selector_Name (Lhs)));
910 begin
911 if Ekind (Comp_Id) = E_Component
912 and then Nkind (Parent (Comp_Id))
913 = N_Component_Declaration
914 and then No (Expression (Parent (Comp_Id)))
915 then
916 return True;
917 end if;
918 return False;
919 end;
921 -- We are assigning to a component of an array
922 -- (and we tested for both Default_Value and
923 -- Default_Component_Value above), so return True.
925 else
926 pragma Assert (Nkind (Lhs) = N_Indexed_Component);
927 return True;
928 end if;
929 end;
930 end Omit_Range_Check_For_Streaming;
932 begin
933 if not Omit_Range_Check_For_Streaming then
934 Apply_Scalar_Range_Check (Rhs, Etype (Lhs));
935 end if;
936 end;
938 -- For array types, verify that lengths match. If the right hand side
939 -- is a function call that has been inlined, the assignment has been
940 -- rewritten as a block, and the constraint check will be applied to the
941 -- assignment within the block.
943 elsif Is_Array_Type (T1)
944 and then (Nkind (Rhs) /= N_Type_Conversion
945 or else Is_Constrained (Etype (Rhs)))
946 and then (Nkind (Rhs) /= N_Function_Call
947 or else Nkind (N) /= N_Block_Statement)
948 then
949 -- Assignment verifies that the length of the Lhs and Rhs are equal,
950 -- but of course the indexes do not have to match. If the right-hand
951 -- side is a type conversion to an unconstrained type, a length check
952 -- is performed on the expression itself during expansion. In rare
953 -- cases, the redundant length check is computed on an index type
954 -- with a different representation, triggering incorrect code in the
955 -- back end.
957 Apply_Length_Check_On_Assignment (Rhs, Etype (Lhs), Lhs);
959 else
960 -- Discriminant checks are applied in the course of expansion
962 null;
963 end if;
965 -- Note: modifications of the Lhs may only be recorded after
966 -- checks have been applied.
968 Note_Possible_Modification (Lhs, Sure => True);
970 -- ??? a real accessibility check is needed when ???
972 -- Post warning for redundant assignment or variable to itself
974 if Warn_On_Redundant_Constructs
976 -- We only warn for source constructs
978 and then Comes_From_Source (N)
980 -- Where the object is the same on both sides
982 and then Same_Object (Lhs, Rhs)
984 -- But exclude the case where the right side was an operation that
985 -- got rewritten (e.g. JUNK + K, where K was known to be zero). We
986 -- don't want to warn in such a case, since it is reasonable to write
987 -- such expressions especially when K is defined symbolically in some
988 -- other package.
990 and then Nkind (Original_Node (Rhs)) not in N_Op
991 then
992 if Nkind (Lhs) in N_Has_Entity then
993 Error_Msg_NE -- CODEFIX
994 ("?r?useless assignment of & to itself!", N, Entity (Lhs));
995 else
996 Error_Msg_N -- CODEFIX
997 ("?r?useless assignment of object to itself!", N);
998 end if;
999 end if;
1001 -- Check for non-allowed composite assignment
1003 if not Support_Composite_Assign_On_Target
1004 and then (Is_Array_Type (T1) or else Is_Record_Type (T1))
1005 and then (not Has_Size_Clause (T1)
1006 or else Esize (T1) > Ttypes.System_Max_Integer_Size)
1007 then
1008 Error_Msg_CRT ("composite assignment", N);
1009 end if;
1011 -- Check elaboration warning for left side if not in elab code
1013 if Legacy_Elaboration_Checks
1014 and not In_Subprogram_Or_Concurrent_Unit
1015 then
1016 Check_Elab_Assign (Lhs);
1017 end if;
1019 -- Save the scenario for later examination by the ABE Processing phase
1021 Record_Elaboration_Scenario (N);
1023 -- Set Referenced_As_LHS if appropriate. We are not interested in
1024 -- compiler-generated assignment statements, nor in references outside
1025 -- the extended main source unit. We check whether the Original_Node is
1026 -- in the extended main source unit because in the case of a renaming of
1027 -- a component of a packed array, the Lhs itself has a Sloc from the
1028 -- place of the renaming.
1030 if Comes_From_Source (N)
1031 and then (In_Extended_Main_Source_Unit (Lhs)
1032 or else In_Extended_Main_Source_Unit (Original_Node (Lhs)))
1033 then
1034 Set_Referenced_Modified (Lhs, Out_Param => False);
1035 end if;
1037 -- RM 7.3.2 (12/3): An assignment to a view conversion (from a type to
1038 -- one of its ancestors) requires an invariant check. Apply check only
1039 -- if expression comes from source, otherwise it will be applied when
1040 -- value is assigned to source entity. This is not done in GNATprove
1041 -- mode, as GNATprove handles invariant checks itself.
1043 if Nkind (Lhs) = N_Type_Conversion
1044 and then Has_Invariants (Etype (Expression (Lhs)))
1045 and then Comes_From_Source (Expression (Lhs))
1046 and then not GNATprove_Mode
1047 then
1048 Insert_After (N, Make_Invariant_Call (Expression (Lhs)));
1049 end if;
1051 -- Final step. If left side is an entity, then we may be able to reset
1052 -- the current tracked values to new safe values. We only have something
1053 -- to do if the left side is an entity name, and expansion has not
1054 -- modified the node into something other than an assignment, and of
1055 -- course we only capture values if it is safe to do so.
1057 if Is_Entity_Name (Lhs)
1058 and then Nkind (N) = N_Assignment_Statement
1059 then
1060 declare
1061 Ent : constant Entity_Id := Entity (Lhs);
1063 begin
1064 if Safe_To_Capture_Value (N, Ent) then
1066 -- If simple variable on left side, warn if this assignment
1067 -- blots out another one (rendering it useless). We only do
1068 -- this for source assignments, otherwise we can generate bogus
1069 -- warnings when an assignment is rewritten as another
1070 -- assignment, and gets tied up with itself.
1072 -- We also omit the warning if the RHS includes target names,
1073 -- that is to say the Ada 2022 "@" that denotes an instance of
1074 -- the LHS, which indicates that the current value is being
1075 -- used. Note that this implicit reference to the entity on
1076 -- the RHS is not treated as a source reference.
1078 -- There may have been a previous reference to a component of
1079 -- the variable, which in general removes the Last_Assignment
1080 -- field of the variable to indicate a relevant use of the
1081 -- previous assignment.
1083 if Warn_On_Modified_Unread
1084 and then Is_Assignable (Ent)
1085 and then Comes_From_Source (N)
1086 and then In_Extended_Main_Source_Unit (Ent)
1087 and then not Has_Target_Names (N)
1088 then
1089 Warn_On_Useless_Assignment (Ent, N);
1090 end if;
1092 -- If we are assigning an access type and the left side is an
1093 -- entity, then make sure that the Is_Known_[Non_]Null flags
1094 -- properly reflect the state of the entity after assignment.
1096 if Is_Access_Type (T1) then
1097 if Known_Non_Null (Rhs) then
1098 Set_Is_Known_Non_Null (Ent, True);
1100 elsif Known_Null (Rhs)
1101 and then not Can_Never_Be_Null (Ent)
1102 then
1103 Set_Is_Known_Null (Ent, True);
1105 else
1106 Set_Is_Known_Null (Ent, False);
1108 if not Can_Never_Be_Null (Ent) then
1109 Set_Is_Known_Non_Null (Ent, False);
1110 end if;
1111 end if;
1113 -- For discrete types, we may be able to set the current value
1114 -- if the value is known at compile time.
1116 elsif Is_Discrete_Type (T1)
1117 and then Compile_Time_Known_Value (Rhs)
1118 then
1119 Set_Current_Value (Ent, Rhs);
1120 else
1121 Set_Current_Value (Ent, Empty);
1122 end if;
1124 -- If not safe to capture values, kill them
1126 else
1127 Kill_Lhs;
1128 end if;
1129 end;
1130 end if;
1132 -- If assigning to an object in whole or in part, note location of
1133 -- assignment in case no one references value. We only do this for
1134 -- source assignments, otherwise we can generate bogus warnings when an
1135 -- assignment is rewritten as another assignment, and gets tied up with
1136 -- itself.
1138 declare
1139 Ent : constant Entity_Id := Get_Enclosing_Object (Lhs);
1140 begin
1141 if Present (Ent)
1142 and then Safe_To_Capture_Value (N, Ent)
1143 and then Nkind (N) = N_Assignment_Statement
1144 and then Warn_On_Modified_Unread
1145 and then Is_Assignable (Ent)
1146 and then Comes_From_Source (N)
1147 and then In_Extended_Main_Source_Unit (Ent)
1148 then
1149 Set_Last_Assignment (Ent, Lhs);
1150 end if;
1151 end;
1153 Analyze_Dimension (N);
1155 <<Leave>>
1156 Restore_Ghost_Region (Saved_GM, Saved_IGR);
1158 -- If the right-hand side contains target names, expansion has been
1159 -- disabled to prevent expansion that might move target names out of
1160 -- the context of the assignment statement. Restore the expander mode
1161 -- now so that assignment statement can be properly expanded.
1163 if Nkind (N) = N_Assignment_Statement then
1164 if Has_Target_Names (N) then
1165 Expander_Mode_Restore;
1166 Full_Analysis := Save_Full_Analysis;
1167 Current_Assignment := Empty;
1168 end if;
1169 end if;
1170 end Analyze_Assignment;
1172 -----------------------------
1173 -- Analyze_Block_Statement --
1174 -----------------------------
1176 procedure Analyze_Block_Statement (N : Node_Id) is
1177 procedure Install_Return_Entities (Scop : Entity_Id);
1178 -- Install all entities of return statement scope Scop in the visibility
1179 -- chain except for the return object since its entity is reused in a
1180 -- renaming.
1182 -----------------------------
1183 -- Install_Return_Entities --
1184 -----------------------------
1186 procedure Install_Return_Entities (Scop : Entity_Id) is
1187 Id : Entity_Id;
1189 begin
1190 Id := First_Entity (Scop);
1191 while Present (Id) loop
1193 -- Do not install the return object
1195 if Ekind (Id) not in E_Constant | E_Variable
1196 or else not Is_Return_Object (Id)
1197 then
1198 Install_Entity (Id);
1199 end if;
1201 Next_Entity (Id);
1202 end loop;
1203 end Install_Return_Entities;
1205 -- Local constants and variables
1207 Decls : constant List_Id := Declarations (N);
1208 Id : constant Node_Id := Identifier (N);
1209 HSS : constant Node_Id := Handled_Statement_Sequence (N);
1211 Is_BIP_Return_Statement : Boolean;
1213 -- Start of processing for Analyze_Block_Statement
1215 begin
1216 -- If no handled statement sequence is present, things are really messed
1217 -- up, and we just return immediately (defence against previous errors).
1219 if No (HSS) then
1220 Check_Error_Detected;
1221 return;
1222 end if;
1224 -- Detect whether the block is actually a rewritten return statement of
1225 -- a build-in-place function.
1227 Is_BIP_Return_Statement :=
1228 Present (Id)
1229 and then Present (Entity (Id))
1230 and then Ekind (Entity (Id)) = E_Return_Statement
1231 and then Is_Build_In_Place_Function
1232 (Return_Applies_To (Entity (Id)));
1234 -- Normal processing with HSS present
1236 declare
1237 EH : constant List_Id := Exception_Handlers (HSS);
1238 Ent : Entity_Id := Empty;
1239 S : Entity_Id;
1241 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1242 -- Recursively save value of this global, will be restored on exit
1244 begin
1245 -- Initialize unblocked exit count for statements of begin block
1246 -- plus one for each exception handler that is present.
1248 Unblocked_Exit_Count := 1 + List_Length (EH);
1250 -- If a label is present analyze it and mark it as referenced
1252 if Present (Id) then
1253 Analyze (Id);
1254 Ent := Entity (Id);
1256 -- An error defense. If we have an identifier, but no entity, then
1257 -- something is wrong. If previous errors, then just remove the
1258 -- identifier and continue, otherwise raise an exception.
1260 if No (Ent) then
1261 Check_Error_Detected;
1262 Set_Identifier (N, Empty);
1264 else
1265 if Ekind (Ent) = E_Label then
1266 Reinit_Field_To_Zero (Ent, F_Enclosing_Scope);
1267 end if;
1269 Mutate_Ekind (Ent, E_Block);
1270 Generate_Reference (Ent, N, ' ');
1271 Generate_Definition (Ent);
1273 if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
1274 Set_Label_Construct (Parent (Ent), N);
1275 end if;
1276 end if;
1277 end if;
1279 -- If no entity set, create a label entity
1281 if No (Ent) then
1282 Ent := New_Internal_Entity (E_Block, Current_Scope, Sloc (N), 'B');
1283 Set_Identifier (N, New_Occurrence_Of (Ent, Sloc (N)));
1284 Set_Parent (Ent, N);
1285 end if;
1287 Set_Etype (Ent, Standard_Void_Type);
1288 Set_Block_Node (Ent, Identifier (N));
1289 Push_Scope (Ent);
1291 -- The block served as an extended return statement. Ensure that any
1292 -- entities created during the analysis and expansion of the return
1293 -- object declaration are once again visible.
1295 if Is_BIP_Return_Statement then
1296 Install_Return_Entities (Ent);
1297 end if;
1299 if Present (Decls) then
1300 Analyze_Declarations (Decls);
1301 Check_Completion;
1302 Inspect_Deferred_Constant_Completion (Decls);
1303 end if;
1305 Analyze (HSS);
1306 Process_End_Label (HSS, 'e', Ent);
1308 -- If exception handlers are present, then we indicate that enclosing
1309 -- scopes contain a block with handlers. We only need to mark non-
1310 -- generic scopes.
1312 if Present (EH) then
1313 S := Scope (Ent);
1314 loop
1315 Set_Has_Nested_Block_With_Handler (S);
1316 exit when Is_Overloadable (S)
1317 or else Ekind (S) = E_Package
1318 or else Is_Generic_Unit (S);
1319 S := Scope (S);
1320 end loop;
1321 end if;
1323 Check_References (Ent);
1324 Update_Use_Clause_Chain;
1325 End_Scope;
1327 if Unblocked_Exit_Count = 0 then
1328 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1329 Check_Unreachable_Code (N);
1330 else
1331 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1332 end if;
1333 end;
1334 end Analyze_Block_Statement;
1336 --------------------------------
1337 -- Analyze_Compound_Statement --
1338 --------------------------------
1340 procedure Analyze_Compound_Statement (N : Node_Id) is
1341 begin
1342 Analyze_List (Actions (N));
1343 end Analyze_Compound_Statement;
1345 ----------------------------
1346 -- Analyze_Case_Statement --
1347 ----------------------------
1349 procedure Analyze_Case_Statement (N : Node_Id) is
1350 Exp : constant Node_Id := Expression (N);
1352 Statements_Analyzed : Boolean := False;
1353 -- Set True if at least some statement sequences get analyzed. If False
1354 -- on exit, means we had a serious error that prevented full analysis of
1355 -- the case statement, and as a result it is not a good idea to output
1356 -- warning messages about unreachable code.
1358 Is_General_Case_Statement : Boolean := False;
1359 -- Set True (later) if type of case expression is not discrete
1361 procedure Non_Static_Choice_Error (Choice : Node_Id);
1362 -- Error routine invoked by the generic instantiation below when the
1363 -- case statement has a non static choice.
1365 procedure Process_Statements (Alternative : Node_Id);
1366 -- Analyzes the statements associated with a case alternative. Needed
1367 -- by instantiation below.
1369 package Analyze_Case_Choices is new
1370 Generic_Analyze_Choices
1371 (Process_Associated_Node => Process_Statements);
1372 use Analyze_Case_Choices;
1373 -- Instantiation of the generic choice analysis package
1375 package Check_Case_Choices is new
1376 Generic_Check_Choices
1377 (Process_Empty_Choice => No_OP,
1378 Process_Non_Static_Choice => Non_Static_Choice_Error,
1379 Process_Associated_Node => No_OP);
1380 use Check_Case_Choices;
1381 -- Instantiation of the generic choice processing package
1383 -----------------------------
1384 -- Non_Static_Choice_Error --
1385 -----------------------------
1387 procedure Non_Static_Choice_Error (Choice : Node_Id) is
1388 begin
1389 Flag_Non_Static_Expr
1390 ("choice given in case statement is not static!", Choice);
1391 end Non_Static_Choice_Error;
1393 ------------------------
1394 -- Process_Statements --
1395 ------------------------
1397 procedure Process_Statements (Alternative : Node_Id) is
1398 Choices : constant List_Id := Discrete_Choices (Alternative);
1399 Ent : Entity_Id;
1401 begin
1402 if Is_General_Case_Statement then
1403 return;
1404 -- Processing deferred in this case; decls associated with
1405 -- pattern match bindings don't exist yet.
1406 end if;
1408 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1409 Statements_Analyzed := True;
1411 -- An interesting optimization. If the case statement expression
1412 -- is a simple entity, then we can set the current value within an
1413 -- alternative if the alternative has one possible value.
1415 -- case N is
1416 -- when 1 => alpha
1417 -- when 2 | 3 => beta
1418 -- when others => gamma
1420 -- Here we know that N is initially 1 within alpha, but for beta and
1421 -- gamma, we do not know anything more about the initial value.
1423 if Is_Entity_Name (Exp) then
1424 Ent := Entity (Exp);
1426 if Is_Object (Ent) then
1427 if List_Length (Choices) = 1
1428 and then Nkind (First (Choices)) in N_Subexpr
1429 and then Compile_Time_Known_Value (First (Choices))
1430 then
1431 Set_Current_Value (Entity (Exp), First (Choices));
1432 end if;
1434 Analyze_Statements (Statements (Alternative));
1436 -- After analyzing the case, set the current value to empty
1437 -- since we won't know what it is for the next alternative
1438 -- (unless reset by this same circuit), or after the case.
1440 Set_Current_Value (Entity (Exp), Empty);
1441 return;
1442 end if;
1443 end if;
1445 -- Case where expression is not an entity name of an object
1447 Analyze_Statements (Statements (Alternative));
1448 end Process_Statements;
1450 -- Local variables
1452 Exp_Type : Entity_Id;
1453 Exp_Btype : Entity_Id;
1455 Others_Present : Boolean;
1456 -- Indicates if Others was present
1458 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1459 -- Recursively save value of this global, will be restored on exit
1461 -- Start of processing for Analyze_Case_Statement
1463 begin
1464 Analyze (Exp);
1466 -- The expression must be of any discrete type. In rare cases, the
1467 -- expander constructs a case statement whose expression has a private
1468 -- type whose full view is discrete. This can happen when generating
1469 -- a stream operation for a variant type after the type is frozen,
1470 -- when the partial of view of the type of the discriminant is private.
1471 -- In that case, use the full view to analyze case alternatives.
1473 if not Is_Overloaded (Exp)
1474 and then not Comes_From_Source (N)
1475 and then Is_Private_Type (Etype (Exp))
1476 and then Present (Full_View (Etype (Exp)))
1477 and then Is_Discrete_Type (Full_View (Etype (Exp)))
1478 then
1479 Resolve (Exp);
1480 Exp_Type := Full_View (Etype (Exp));
1482 -- For Ada, overloading might be ok because subsequently filtering
1483 -- out non-discretes may resolve the ambiguity.
1484 -- But GNAT extensions allow casing on non-discretes.
1486 elsif All_Extensions_Allowed and then Is_Overloaded (Exp) then
1488 -- It would be nice if we could generate all the right error
1489 -- messages by calling "Resolve (Exp, Any_Type);" in the
1490 -- same way that they are generated a few lines below by the
1491 -- call "Analyze_And_Resolve (Exp, Any_Discrete);".
1492 -- Unfortunately, Any_Type and Any_Discrete are not treated
1493 -- consistently (specifically, by Sem_Type.Covers), so that
1494 -- doesn't work.
1496 Error_Msg_N
1497 ("selecting expression of general case statement is ambiguous",
1498 Exp);
1499 return;
1501 -- Check for a GNAT-extension "general" case statement (i.e., one where
1502 -- the type of the selecting expression is not discrete).
1504 elsif All_Extensions_Allowed
1505 and then not Is_Discrete_Type (Etype (Exp))
1506 then
1507 Resolve (Exp, Etype (Exp));
1508 Exp_Type := Etype (Exp);
1509 Is_General_Case_Statement := True;
1510 if not (Is_Record_Type (Exp_Type) or Is_Array_Type (Exp_Type)) then
1511 Error_Msg_N
1512 ("selecting expression of general case statement " &
1513 "must be a record or an array",
1514 Exp);
1516 -- Avoid cascading errors
1517 return;
1518 end if;
1519 else
1520 Analyze_And_Resolve (Exp, Any_Discrete);
1521 Exp_Type := Etype (Exp);
1522 end if;
1524 Check_Unset_Reference (Exp);
1525 Exp_Btype := Base_Type (Exp_Type);
1527 -- The expression must be of a discrete type which must be determinable
1528 -- independently of the context in which the expression occurs, but
1529 -- using the fact that the expression must be of a discrete type.
1530 -- Moreover, the type this expression must not be a character literal
1531 -- (which is always ambiguous) or, for Ada-83, a generic formal type.
1533 -- If error already reported by Resolve, nothing more to do
1535 if Exp_Btype = Any_Discrete or else Exp_Btype = Any_Type then
1536 return;
1538 elsif Exp_Btype = Any_Character then
1539 Error_Msg_N
1540 ("character literal as case expression is ambiguous", Exp);
1541 return;
1543 elsif Ada_Version = Ada_83
1544 and then (Is_Generic_Type (Exp_Btype)
1545 or else Is_Generic_Type (Root_Type (Exp_Btype)))
1546 then
1547 Error_Msg_N
1548 ("(Ada 83) case expression cannot be of a generic type", Exp);
1549 return;
1551 elsif not All_Extensions_Allowed
1552 and then not Is_Discrete_Type (Exp_Type)
1553 then
1554 Error_Msg_N
1555 ("expression in case statement must be of a discrete_Type", Exp);
1556 return;
1557 end if;
1559 -- If the case expression is a formal object of mode in out, then treat
1560 -- it as having a nonstatic subtype by forcing use of the base type
1561 -- (which has to get passed to Check_Case_Choices below). Also use base
1562 -- type when the case expression is parenthesized.
1564 if Paren_Count (Exp) > 0
1565 or else (Is_Entity_Name (Exp)
1566 and then Ekind (Entity (Exp)) = E_Generic_In_Out_Parameter)
1567 then
1568 Exp_Type := Exp_Btype;
1569 end if;
1571 -- Call instantiated procedures to analyze and check discrete choices
1573 Unblocked_Exit_Count := 0;
1575 Analyze_Choices (Alternatives (N), Exp_Type);
1576 Check_Choices (N, Alternatives (N), Exp_Type, Others_Present);
1578 if Is_General_Case_Statement then
1579 -- Work normally done in Process_Statements was deferred; do that
1580 -- deferred work now that Check_Choices has had a chance to create
1581 -- any needed pattern-match-binding declarations.
1582 declare
1583 Alt : Node_Id := First (Alternatives (N));
1584 begin
1585 while Present (Alt) loop
1586 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1587 Analyze_Statements (Statements (Alt));
1588 Next (Alt);
1589 end loop;
1590 end;
1591 end if;
1593 if Exp_Type = Universal_Integer and then not Others_Present then
1594 Error_Msg_N ("case on universal integer requires OTHERS choice", Exp);
1595 end if;
1597 -- If all our exits were blocked by unconditional transfers of control,
1598 -- then the entire CASE statement acts as an unconditional transfer of
1599 -- control, so treat it like one, and check unreachable code. Skip this
1600 -- test if we had serious errors preventing any statement analysis.
1602 if Unblocked_Exit_Count = 0 and then Statements_Analyzed then
1603 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1604 Check_Unreachable_Code (N);
1605 else
1606 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1607 end if;
1609 -- If the expander is active it will detect the case of a statically
1610 -- determined single alternative and remove warnings for the case, but
1611 -- if we are not doing expansion, that circuit won't be active. Here we
1612 -- duplicate the effect of removing warnings in the same way, so that
1613 -- we will get the same set of warnings in -gnatc mode.
1615 if not Expander_Active
1616 and then Compile_Time_Known_Value (Expression (N))
1617 and then Serious_Errors_Detected = 0
1618 then
1619 declare
1620 Chosen : constant Node_Id := Find_Static_Alternative (N);
1621 Alt : Node_Id;
1623 begin
1624 Alt := First (Alternatives (N));
1625 while Present (Alt) loop
1626 if Alt /= Chosen then
1627 Remove_Warning_Messages (Statements (Alt));
1628 end if;
1630 Next (Alt);
1631 end loop;
1632 end;
1633 end if;
1634 end Analyze_Case_Statement;
1636 ----------------------------
1637 -- Analyze_Exit_Statement --
1638 ----------------------------
1640 -- If the exit includes a name, it must be the name of a currently open
1641 -- loop. Otherwise there must be an innermost open loop on the stack, to
1642 -- which the statement implicitly refers.
1644 -- Additionally, in SPARK mode:
1646 -- The exit can only name the closest enclosing loop;
1648 -- An exit with a when clause must be directly contained in a loop;
1650 -- An exit without a when clause must be directly contained in an
1651 -- if-statement with no elsif or else, which is itself directly contained
1652 -- in a loop. The exit must be the last statement in the if-statement.
1654 procedure Analyze_Exit_Statement (N : Node_Id) is
1655 Target : constant Node_Id := Name (N);
1656 Cond : constant Node_Id := Condition (N);
1657 Scope_Id : Entity_Id := Empty; -- initialize to prevent warning
1658 U_Name : Entity_Id;
1659 Kind : Entity_Kind;
1661 begin
1662 if No (Cond) then
1663 Check_Unreachable_Code (N);
1664 end if;
1666 if Present (Target) then
1667 Analyze (Target);
1668 U_Name := Entity (Target);
1670 if not In_Open_Scopes (U_Name) or else Ekind (U_Name) /= E_Loop then
1671 Error_Msg_N ("invalid loop name in exit statement", N);
1672 return;
1674 else
1675 Set_Has_Exit (U_Name);
1676 end if;
1678 else
1679 U_Name := Empty;
1680 end if;
1682 for J in reverse 0 .. Scope_Stack.Last loop
1683 Scope_Id := Scope_Stack.Table (J).Entity;
1684 Kind := Ekind (Scope_Id);
1686 if Kind = E_Loop and then (No (Target) or else Scope_Id = U_Name) then
1687 Set_Has_Exit (Scope_Id);
1688 exit;
1690 elsif Kind = E_Block
1691 or else Kind = E_Loop
1692 or else Kind = E_Return_Statement
1693 then
1694 null;
1696 else
1697 Error_Msg_N
1698 ("cannot exit from program unit or accept statement", N);
1699 return;
1700 end if;
1701 end loop;
1703 -- Verify that if present the condition is a Boolean expression
1705 if Present (Cond) then
1706 Analyze_And_Resolve (Cond, Any_Boolean);
1707 Check_Unset_Reference (Cond);
1708 end if;
1710 -- Chain exit statement to associated loop entity
1712 Set_Next_Exit_Statement (N, First_Exit_Statement (Scope_Id));
1713 Set_First_Exit_Statement (Scope_Id, N);
1715 -- Since the exit may take us out of a loop, any previous assignment
1716 -- statement is not useless, so clear last assignment indications. It
1717 -- is OK to keep other current values, since if the exit statement
1718 -- does not exit, then the current values are still valid.
1720 Kill_Current_Values (Last_Assignment_Only => True);
1721 end Analyze_Exit_Statement;
1723 ----------------------------
1724 -- Analyze_Goto_Statement --
1725 ----------------------------
1727 procedure Analyze_Goto_Statement (N : Node_Id) is
1728 Label : constant Node_Id := Name (N);
1729 Scope_Id : Entity_Id;
1730 Label_Scope : Entity_Id;
1731 Label_Ent : Entity_Id;
1733 begin
1734 -- Actual semantic checks
1736 Check_Unreachable_Code (N);
1737 Kill_Current_Values (Last_Assignment_Only => True);
1739 Analyze (Label);
1740 Label_Ent := Entity (Label);
1742 -- Ignore previous error
1744 if Label_Ent = Any_Id then
1745 Check_Error_Detected;
1746 return;
1748 -- We just have a label as the target of a goto
1750 elsif Ekind (Label_Ent) /= E_Label then
1751 Error_Msg_N ("target of goto statement must be a label", Label);
1752 return;
1754 -- Check that the target of the goto is reachable according to Ada
1755 -- scoping rules. Note: the special gotos we generate for optimizing
1756 -- local handling of exceptions would violate these rules, but we mark
1757 -- such gotos as analyzed when built, so this code is never entered.
1759 elsif not Reachable (Label_Ent) then
1760 Error_Msg_N ("target of goto statement is not reachable", Label);
1761 return;
1762 end if;
1764 -- Here if goto passes initial validity checks
1766 Label_Scope := Enclosing_Scope (Label_Ent);
1768 for J in reverse 0 .. Scope_Stack.Last loop
1769 Scope_Id := Scope_Stack.Table (J).Entity;
1771 if Label_Scope = Scope_Id
1772 or else Ekind (Scope_Id) not in
1773 E_Block | E_Loop | E_Return_Statement
1774 then
1775 if Scope_Id /= Label_Scope then
1776 Error_Msg_N
1777 ("cannot exit from program unit or accept statement", N);
1778 end if;
1780 return;
1781 end if;
1782 end loop;
1784 raise Program_Error;
1785 end Analyze_Goto_Statement;
1787 ---------------------------------
1788 -- Analyze_Goto_When_Statement --
1789 ---------------------------------
1791 procedure Analyze_Goto_When_Statement (N : Node_Id) is
1792 begin
1793 -- Verify the condition is a Boolean expression
1795 Analyze_And_Resolve (Condition (N), Any_Boolean);
1796 Check_Unset_Reference (Condition (N));
1797 end Analyze_Goto_When_Statement;
1799 --------------------------
1800 -- Analyze_If_Statement --
1801 --------------------------
1803 -- A special complication arises in the analysis of if statements
1805 -- The expander has circuitry to completely delete code that it can tell
1806 -- will not be executed (as a result of compile time known conditions). In
1807 -- the analyzer, we ensure that code that will be deleted in this manner
1808 -- is analyzed but not expanded. This is obviously more efficient, but
1809 -- more significantly, difficulties arise if code is expanded and then
1810 -- eliminated (e.g. exception table entries disappear). Similarly, itypes
1811 -- generated in deleted code must be frozen from start, because the nodes
1812 -- on which they depend will not be available at the freeze point.
1814 procedure Analyze_If_Statement (N : Node_Id) is
1815 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1816 -- Recursively save value of this global, will be restored on exit
1818 Save_In_Deleted_Code : Boolean := In_Deleted_Code;
1820 Del : Boolean := False;
1821 -- This flag gets set True if a True condition has been found, which
1822 -- means that remaining ELSE/ELSIF parts are deleted.
1824 procedure Analyze_Cond_Then (Cnode : Node_Id);
1825 -- This is applied to either the N_If_Statement node itself or to an
1826 -- N_Elsif_Part node. It deals with analyzing the condition and the THEN
1827 -- statements associated with it.
1829 -----------------------
1830 -- Analyze_Cond_Then --
1831 -----------------------
1833 procedure Analyze_Cond_Then (Cnode : Node_Id) is
1834 Cond : constant Node_Id := Condition (Cnode);
1835 Tstm : constant List_Id := Then_Statements (Cnode);
1837 begin
1838 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1839 Analyze_And_Resolve (Cond, Any_Boolean);
1840 Check_Unset_Reference (Cond);
1841 Set_Current_Value_Condition (Cnode);
1843 -- If already deleting, then just analyze then statements
1845 if Del then
1846 Analyze_Statements (Tstm);
1848 -- Compile time known value, not deleting yet
1850 elsif Compile_Time_Known_Value (Cond) then
1851 Save_In_Deleted_Code := In_Deleted_Code;
1853 -- If condition is True, then analyze the THEN statements and set
1854 -- no expansion for ELSE and ELSIF parts.
1856 if Is_True (Expr_Value (Cond)) then
1857 Analyze_Statements (Tstm);
1858 Del := True;
1859 Expander_Mode_Save_And_Set (False);
1860 In_Deleted_Code := True;
1862 -- If condition is False, analyze THEN with expansion off
1864 else pragma Assert (Is_False (Expr_Value (Cond)));
1865 Expander_Mode_Save_And_Set (False);
1866 In_Deleted_Code := True;
1867 Analyze_Statements (Tstm);
1868 Expander_Mode_Restore;
1869 In_Deleted_Code := Save_In_Deleted_Code;
1870 end if;
1872 -- Not known at compile time, not deleting, normal analysis
1874 else
1875 Analyze_Statements (Tstm);
1876 end if;
1877 end Analyze_Cond_Then;
1879 -- Local variables
1881 E : Node_Id;
1882 -- For iterating over elsif parts
1884 -- Start of processing for Analyze_If_Statement
1886 begin
1887 -- Initialize exit count for else statements. If there is no else part,
1888 -- this count will stay non-zero reflecting the fact that the uncovered
1889 -- else case is an unblocked exit.
1891 Unblocked_Exit_Count := 1;
1892 Analyze_Cond_Then (N);
1894 -- Now to analyze the elsif parts if any are present
1896 E := First (Elsif_Parts (N));
1897 while Present (E) loop
1898 Analyze_Cond_Then (E);
1899 Next (E);
1900 end loop;
1902 if Present (Else_Statements (N)) then
1903 Analyze_Statements (Else_Statements (N));
1904 end if;
1906 -- If all our exits were blocked by unconditional transfers of control,
1907 -- then the entire IF statement acts as an unconditional transfer of
1908 -- control, so treat it like one, and check unreachable code.
1910 if Unblocked_Exit_Count = 0 then
1911 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1912 Check_Unreachable_Code (N);
1913 else
1914 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1915 end if;
1917 if Del then
1918 Expander_Mode_Restore;
1919 In_Deleted_Code := Save_In_Deleted_Code;
1920 end if;
1922 if not Expander_Active
1923 and then Compile_Time_Known_Value (Condition (N))
1924 and then Serious_Errors_Detected = 0
1925 then
1926 if Is_True (Expr_Value (Condition (N))) then
1927 Remove_Warning_Messages (Else_Statements (N));
1929 E := First (Elsif_Parts (N));
1930 while Present (E) loop
1931 Remove_Warning_Messages (Then_Statements (E));
1932 Next (E);
1933 end loop;
1935 else
1936 Remove_Warning_Messages (Then_Statements (N));
1937 end if;
1938 end if;
1940 -- Warn on redundant if statement that has no effect
1942 -- Note, we could also check empty ELSIF parts ???
1944 if Warn_On_Redundant_Constructs
1946 -- If statement must be from source
1948 and then Comes_From_Source (N)
1950 -- Condition must not have obvious side effect
1952 and then Has_No_Obvious_Side_Effects (Condition (N))
1954 -- No elsif parts of else part
1956 and then No (Elsif_Parts (N))
1957 and then No (Else_Statements (N))
1959 -- Then must be a single null statement
1961 and then List_Length (Then_Statements (N)) = 1
1962 then
1963 -- Go to original node, since we may have rewritten something as
1964 -- a null statement (e.g. a case we could figure the outcome of).
1966 declare
1967 T : constant Node_Id := First (Then_Statements (N));
1968 S : constant Node_Id := Original_Node (T);
1970 begin
1971 if Comes_From_Source (S) and then Nkind (S) = N_Null_Statement then
1972 Error_Msg_N ("if statement has no effect?r?", N);
1973 end if;
1974 end;
1975 end if;
1976 end Analyze_If_Statement;
1978 ----------------------------------------
1979 -- Analyze_Implicit_Label_Declaration --
1980 ----------------------------------------
1982 -- An implicit label declaration is generated in the innermost enclosing
1983 -- declarative part. This is done for labels, and block and loop names.
1985 procedure Analyze_Implicit_Label_Declaration (N : Node_Id) is
1986 Id : constant Node_Id := Defining_Identifier (N);
1987 begin
1988 Enter_Name (Id);
1989 Mutate_Ekind (Id, E_Label);
1990 Set_Etype (Id, Standard_Void_Type);
1991 Set_Enclosing_Scope (Id, Current_Scope);
1993 -- A label declared within a Ghost region becomes Ghost (SPARK RM
1994 -- 6.9(2)).
1996 if Ghost_Mode > None then
1997 Set_Is_Ghost_Entity (Id);
1998 end if;
1999 end Analyze_Implicit_Label_Declaration;
2001 ------------------------------
2002 -- Analyze_Iteration_Scheme --
2003 ------------------------------
2005 procedure Analyze_Iteration_Scheme (N : Node_Id) is
2006 Cond : Node_Id;
2007 Iter_Spec : Node_Id;
2008 Loop_Spec : Node_Id;
2010 begin
2011 -- For an infinite loop, there is no iteration scheme
2013 if No (N) then
2014 return;
2015 end if;
2017 Cond := Condition (N);
2018 Iter_Spec := Iterator_Specification (N);
2019 Loop_Spec := Loop_Parameter_Specification (N);
2021 if Present (Cond) then
2022 Analyze_And_Resolve (Cond, Any_Boolean);
2023 Check_Unset_Reference (Cond);
2024 Set_Current_Value_Condition (N);
2026 elsif Present (Iter_Spec) then
2027 Analyze_Iterator_Specification (Iter_Spec);
2029 else
2030 Analyze_Loop_Parameter_Specification (Loop_Spec);
2031 end if;
2032 end Analyze_Iteration_Scheme;
2034 ------------------------------------
2035 -- Analyze_Iterator_Specification --
2036 ------------------------------------
2038 procedure Analyze_Iterator_Specification (N : Node_Id) is
2039 Def_Id : constant Node_Id := Defining_Identifier (N);
2040 Iter_Name : constant Node_Id := Name (N);
2041 Loc : constant Source_Ptr := Sloc (N);
2042 Subt : constant Node_Id := Subtype_Indication (N);
2044 Bas : Entity_Id := Empty; -- initialize to prevent warning
2045 Typ : Entity_Id;
2047 procedure Check_Reverse_Iteration (Typ : Entity_Id);
2048 -- For an iteration over a container, if the loop carries the Reverse
2049 -- indicator, verify that the container type has an Iterate aspect that
2050 -- implements the reversible iterator interface.
2052 procedure Check_Subtype_Definition (Comp_Type : Entity_Id);
2053 -- If a subtype indication is present, verify that it is consistent
2054 -- with the component type of the array or container name.
2055 -- In Ada 2022, the subtype indication may be an access definition,
2056 -- if the array or container has elements of an anonymous access type.
2058 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id;
2059 -- For containers with Iterator and related aspects, the cursor is
2060 -- obtained by locating an entity with the proper name in the scope
2061 -- of the type.
2063 -----------------------------
2064 -- Check_Reverse_Iteration --
2065 -----------------------------
2067 procedure Check_Reverse_Iteration (Typ : Entity_Id) is
2068 begin
2069 if Reverse_Present (N) then
2070 if Is_Array_Type (Typ)
2071 or else Is_Reversible_Iterator (Typ)
2072 or else
2073 (Has_Aspect (Typ, Aspect_Iterable)
2074 and then
2075 Present
2076 (Get_Iterable_Type_Primitive (Typ, Name_Previous)))
2077 then
2078 null;
2079 else
2080 Error_Msg_N
2081 ("container type does not support reverse iteration", N);
2082 end if;
2083 end if;
2084 end Check_Reverse_Iteration;
2086 -------------------------------
2087 -- Check_Subtype_Definition --
2088 -------------------------------
2090 procedure Check_Subtype_Definition (Comp_Type : Entity_Id) is
2091 begin
2092 if No (Subt) then
2093 return;
2094 end if;
2096 if Is_Anonymous_Access_Type (Entity (Subt)) then
2097 if not Is_Anonymous_Access_Type (Comp_Type) then
2098 Error_Msg_NE
2099 ("component type& is not an anonymous access",
2100 Subt, Comp_Type);
2102 elsif not Conforming_Types
2103 (Designated_Type (Entity (Subt)),
2104 Designated_Type (Comp_Type),
2105 Fully_Conformant)
2106 then
2107 Error_Msg_NE
2108 ("subtype indication does not match component type&",
2109 Subt, Comp_Type);
2110 end if;
2112 elsif not Covers (Base_Type (Bas), Comp_Type)
2113 or else not Subtypes_Statically_Match (Bas, Comp_Type)
2114 then
2115 if Is_Array_Type (Typ) then
2116 Error_Msg_NE
2117 ("subtype indication does not match component type&",
2118 Subt, Comp_Type);
2119 else
2120 Error_Msg_NE
2121 ("subtype indication does not match element type&",
2122 Subt, Comp_Type);
2123 end if;
2124 end if;
2125 end Check_Subtype_Definition;
2127 ---------------------
2128 -- Get_Cursor_Type --
2129 ---------------------
2131 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id is
2132 Ent : Entity_Id;
2134 begin
2135 -- If the iterator type is derived and it has an iterator interface
2136 -- type as an ancestor, then the cursor type is declared in the scope
2137 -- of that interface type.
2139 if Is_Derived_Type (Typ) then
2140 declare
2141 Iter_Iface : constant Entity_Id :=
2142 Iterator_Interface_Ancestor (Typ);
2144 begin
2145 if Present (Iter_Iface) then
2146 Ent := First_Entity (Scope (Iter_Iface));
2148 -- If there's not an iterator interface, then retrieve the
2149 -- scope associated with the parent type and start from its
2150 -- first entity.
2152 else
2153 Ent := First_Entity (Scope (Etype (Typ)));
2154 end if;
2155 end;
2157 else
2158 Ent := First_Entity (Scope (Typ));
2159 end if;
2161 while Present (Ent) loop
2162 exit when Chars (Ent) = Name_Cursor;
2163 Next_Entity (Ent);
2164 end loop;
2166 if No (Ent) then
2167 return Any_Type;
2168 end if;
2170 -- The cursor is the target of generated assignments in the
2171 -- loop, and cannot have a limited type.
2173 if Is_Limited_Type (Etype (Ent)) then
2174 Error_Msg_N ("cursor type cannot be limited", N);
2175 end if;
2177 return Etype (Ent);
2178 end Get_Cursor_Type;
2180 -- Start of processing for Analyze_Iterator_Specification
2182 begin
2183 Enter_Name (Def_Id);
2185 -- AI12-0151 specifies that when the subtype indication is present, it
2186 -- must statically match the type of the array or container element.
2187 -- To simplify this check, we introduce a subtype declaration with the
2188 -- given subtype indication when it carries a constraint, and rewrite
2189 -- the original as a reference to the created subtype entity.
2191 if Present (Subt) then
2192 if Nkind (Subt) = N_Subtype_Indication then
2193 declare
2194 S : constant Entity_Id := Make_Temporary (Sloc (Subt), 'S');
2195 Decl : constant Node_Id :=
2196 Make_Subtype_Declaration (Loc,
2197 Defining_Identifier => S,
2198 Subtype_Indication => New_Copy_Tree (Subt));
2199 begin
2200 Insert_Action (N, Decl);
2201 Analyze (Decl);
2202 Rewrite (Subt, New_Occurrence_Of (S, Sloc (Subt)));
2203 end;
2205 -- Ada 2022: the subtype definition may be for an anonymous
2206 -- access type.
2208 elsif Nkind (Subt) = N_Access_Definition then
2209 declare
2210 S : constant Entity_Id := Make_Temporary (Sloc (Subt), 'S');
2211 Decl : Node_Id;
2212 begin
2213 if Present (Subtype_Mark (Subt)) then
2214 Decl :=
2215 Make_Full_Type_Declaration (Loc,
2216 Defining_Identifier => S,
2217 Type_Definition =>
2218 Make_Access_To_Object_Definition (Loc,
2219 All_Present => True,
2220 Subtype_Indication =>
2221 New_Copy_Tree (Subtype_Mark (Subt))));
2223 else
2224 Decl :=
2225 Make_Full_Type_Declaration (Loc,
2226 Defining_Identifier => S,
2227 Type_Definition =>
2228 New_Copy_Tree
2229 (Access_To_Subprogram_Definition (Subt)));
2230 end if;
2232 Insert_Before (Parent (Parent (N)), Decl);
2233 Analyze (Decl);
2234 Freeze_Before (First (Statements (Parent (Parent (N)))), S);
2235 Rewrite (Subt, New_Occurrence_Of (S, Sloc (Subt)));
2236 end;
2237 else
2238 Analyze (Subt);
2239 end if;
2241 -- Save entity of subtype indication for subsequent check
2243 Bas := Entity (Subt);
2244 end if;
2246 Preanalyze_Range (Iter_Name);
2248 -- If the domain of iteration is a function call, make sure the function
2249 -- itself is frozen. This is an issue if this is a local expression
2250 -- function.
2252 if Nkind (Iter_Name) = N_Function_Call
2253 and then Is_Entity_Name (Name (Iter_Name))
2254 and then Full_Analysis
2255 and then (In_Assertion_Expr = 0 or else Assertions_Enabled)
2256 then
2257 Freeze_Before (N, Entity (Name (Iter_Name)));
2258 end if;
2260 -- Set the kind of the loop variable, which is not visible within the
2261 -- iterator name.
2263 Mutate_Ekind (Def_Id, E_Variable);
2264 Set_Is_Not_Self_Hidden (Def_Id);
2266 -- Provide a link between the iterator variable and the container, for
2267 -- subsequent use in cross-reference and modification information.
2269 if Of_Present (N) then
2270 Set_Related_Expression (Def_Id, Iter_Name);
2272 -- For a container, the iterator is specified through the aspect
2274 if not Is_Array_Type (Etype (Iter_Name)) then
2275 declare
2276 Iterator : constant Entity_Id :=
2277 Find_Value_Of_Aspect
2278 (Etype (Iter_Name), Aspect_Default_Iterator);
2280 I : Interp_Index;
2281 It : Interp;
2283 begin
2284 -- The domain of iteration must implement either the RM
2285 -- iterator interface, or the SPARK Iterable aspect.
2287 if No (Iterator) then
2288 if No (Find_Aspect (Etype (Iter_Name), Aspect_Iterable)) then
2289 Error_Msg_NE
2290 ("cannot iterate over&",
2291 N, Base_Type (Etype (Iter_Name)));
2292 return;
2293 end if;
2295 elsif not Is_Overloaded (Iterator) then
2296 Check_Reverse_Iteration (Etype (Iterator));
2298 -- If Iterator is overloaded, use reversible iterator if one is
2299 -- available.
2301 elsif Is_Overloaded (Iterator) then
2302 Get_First_Interp (Iterator, I, It);
2303 while Present (It.Nam) loop
2304 if Ekind (It.Nam) = E_Function
2305 and then Is_Reversible_Iterator (Etype (It.Nam))
2306 then
2307 Set_Etype (Iterator, It.Typ);
2308 Set_Entity (Iterator, It.Nam);
2309 exit;
2310 end if;
2312 Get_Next_Interp (I, It);
2313 end loop;
2315 Check_Reverse_Iteration (Etype (Iterator));
2316 end if;
2317 end;
2318 end if;
2319 end if;
2321 -- If the domain of iteration is an expression, create a declaration for
2322 -- it, so that finalization actions are introduced outside of the loop.
2323 -- The declaration must be a renaming (both in GNAT and GNATprove
2324 -- modes), because the body of the loop may assign to elements.
2326 if not Is_Entity_Name (Iter_Name)
2328 -- Do not perform this expansion in preanalysis
2330 and then Full_Analysis
2332 -- Do not perform this expansion when expansion is disabled, where the
2333 -- temporary may hide the transformation of a selected component into
2334 -- a prefixed function call, and references need to see the original
2335 -- expression.
2337 and then (Expander_Active or GNATprove_Mode)
2338 then
2339 declare
2340 Id : constant Entity_Id := Make_Temporary (Loc, 'R', Iter_Name);
2341 Decl : Node_Id;
2342 Act_S : Node_Id;
2344 begin
2346 -- If the domain of iteration is an array component that depends
2347 -- on a discriminant, create actual subtype for it. Preanalysis
2348 -- does not generate the actual subtype of a selected component.
2350 if Nkind (Iter_Name) = N_Selected_Component
2351 and then Is_Array_Type (Etype (Iter_Name))
2352 then
2353 Act_S :=
2354 Build_Actual_Subtype_Of_Component
2355 (Etype (Selector_Name (Iter_Name)), Iter_Name);
2356 Insert_Action (N, Act_S);
2358 if Present (Act_S) then
2359 Typ := Defining_Identifier (Act_S);
2360 else
2361 Typ := Etype (Iter_Name);
2362 end if;
2364 else
2365 Typ := Etype (Iter_Name);
2367 -- Verify that the expression produces an iterator
2369 if not Of_Present (N) and then not Is_Iterator (Typ)
2370 and then not Is_Array_Type (Typ)
2371 and then No (Find_Aspect (Typ, Aspect_Iterable))
2372 then
2373 Error_Msg_N
2374 ("expect object that implements iterator interface",
2375 Iter_Name);
2376 end if;
2377 end if;
2379 -- Protect against malformed iterator
2381 if Typ = Any_Type then
2382 Error_Msg_N ("invalid expression in loop iterator", Iter_Name);
2383 return;
2384 end if;
2386 if not Of_Present (N) then
2387 Check_Reverse_Iteration (Typ);
2388 end if;
2390 -- For an element iteration over a slice, we must complete
2391 -- the resolution and expansion of the slice bounds. These
2392 -- can be arbitrary expressions, and the preanalysis that
2393 -- was performed in preparation for the iteration may have
2394 -- generated an itype whose bounds must be fully expanded.
2395 -- We set the parent node to provide a proper insertion
2396 -- point for generated actions, if any.
2398 if Nkind (Iter_Name) = N_Slice
2399 and then Nkind (Discrete_Range (Iter_Name)) = N_Range
2400 and then not Analyzed (Discrete_Range (Iter_Name))
2401 then
2402 declare
2403 Indx : constant Node_Id :=
2404 Entity (First_Index (Etype (Iter_Name)));
2405 begin
2406 Set_Parent (Indx, Iter_Name);
2407 Resolve (Scalar_Range (Indx), Etype (Indx));
2408 end;
2409 end if;
2411 -- The name in the renaming declaration may be a function call.
2412 -- Indicate that it does not come from source, to suppress
2413 -- spurious warnings on renamings of parameterless functions,
2414 -- a common enough idiom in user-defined iterators.
2416 Decl :=
2417 Make_Object_Renaming_Declaration (Loc,
2418 Defining_Identifier => Id,
2419 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
2420 Name =>
2421 New_Copy_Tree (Iter_Name, New_Sloc => Loc));
2422 Set_Comes_From_Iterator (Decl);
2424 Insert_Actions (Parent (Parent (N)), New_List (Decl));
2425 Rewrite (Name (N), New_Occurrence_Of (Id, Loc));
2426 Analyze (Name (N));
2427 Set_Etype (Id, Typ);
2428 Set_Etype (Name (N), Typ);
2429 end;
2431 -- Container is an entity or an array with uncontrolled components, or
2432 -- else it is a container iterator given by a function call, typically
2433 -- called Iterate in the case of predefined containers, even though
2434 -- Iterate is not a reserved name. What matters is that the return type
2435 -- of the function is an iterator type.
2437 elsif Is_Entity_Name (Iter_Name) then
2438 Analyze (Iter_Name);
2440 if Nkind (Iter_Name) = N_Function_Call then
2441 declare
2442 C : constant Node_Id := Name (Iter_Name);
2443 I : Interp_Index;
2444 It : Interp;
2446 begin
2447 if not Is_Overloaded (Iter_Name) then
2448 Resolve (Iter_Name, Etype (C));
2450 else
2451 Get_First_Interp (C, I, It);
2452 while It.Typ /= Empty loop
2453 if Reverse_Present (N) then
2454 if Is_Reversible_Iterator (It.Typ) then
2455 Resolve (Iter_Name, It.Typ);
2456 exit;
2457 end if;
2459 elsif Is_Iterator (It.Typ) then
2460 Resolve (Iter_Name, It.Typ);
2461 exit;
2462 end if;
2464 Get_Next_Interp (I, It);
2465 end loop;
2466 end if;
2467 end;
2469 -- Domain of iteration is not overloaded
2471 else
2472 Resolve (Iter_Name);
2473 end if;
2475 if not Of_Present (N) then
2476 Check_Reverse_Iteration (Etype (Iter_Name));
2477 end if;
2478 end if;
2480 -- Get base type of container, for proper retrieval of Cursor type
2481 -- and primitive operations.
2483 Typ := Base_Type (Etype (Iter_Name));
2485 if Is_Array_Type (Typ) then
2486 if Of_Present (N) then
2487 Set_Etype (Def_Id, Component_Type (Typ));
2489 -- The loop variable is aliased if the array components are
2490 -- aliased. Likewise for the independent aspect.
2492 Set_Is_Aliased (Def_Id, Has_Aliased_Components (Typ));
2493 Set_Is_Independent (Def_Id, Has_Independent_Components (Typ));
2495 -- AI12-0047 stipulates that the domain (array or container)
2496 -- cannot be a component that depends on a discriminant if the
2497 -- enclosing object is mutable, to prevent a modification of the
2498 -- domain of iteration in the course of an iteration.
2500 -- If the object is an expression it has been captured in a
2501 -- temporary, so examine original node.
2503 if Nkind (Original_Node (Iter_Name)) = N_Selected_Component
2504 and then Is_Dependent_Component_Of_Mutable_Object
2505 (Original_Node (Iter_Name))
2506 then
2507 Error_Msg_N
2508 ("iterable name cannot be a discriminant-dependent "
2509 & "component of a mutable object", N);
2511 elsif Depends_On_Mutably_Tagged_Ext_Comp
2512 (Original_Node (Iter_Name))
2513 then
2514 Error_Msg_N
2515 ("iterable name cannot depend on a mutably tagged component",
2517 end if;
2519 Check_Subtype_Definition (Component_Type (Typ));
2521 -- Here we have a missing Range attribute
2523 else
2524 Error_Msg_N
2525 ("missing Range attribute in iteration over an array", N);
2527 -- In Ada 2012 mode, this may be an attempt at an iterator
2529 if Ada_Version >= Ada_2012 then
2530 Error_Msg_NE
2531 ("\if& is meant to designate an element of the array, use OF",
2532 N, Def_Id);
2533 end if;
2535 -- Prevent cascaded errors
2537 Mutate_Ekind (Def_Id, E_Loop_Parameter);
2538 Set_Etype (Def_Id, Etype (First_Index (Typ)));
2539 end if;
2541 -- Check for type error in iterator
2543 elsif Typ = Any_Type then
2544 return;
2546 -- Iteration over a container
2548 else
2549 Mutate_Ekind (Def_Id, E_Loop_Parameter);
2550 Set_Is_Not_Self_Hidden (Def_Id);
2551 Error_Msg_Ada_2012_Feature ("container iterator", Sloc (N));
2553 -- OF present
2555 if Of_Present (N) then
2556 if Has_Aspect (Typ, Aspect_Iterable) then
2557 declare
2558 Elt : constant Entity_Id :=
2559 Get_Iterable_Type_Primitive (Typ, Name_Element);
2560 begin
2561 if No (Elt) then
2562 Error_Msg_N
2563 ("missing Element primitive for iteration", N);
2564 else
2565 Set_Etype (Def_Id, Etype (Elt));
2566 Check_Reverse_Iteration (Typ);
2567 end if;
2568 end;
2570 Check_Subtype_Definition (Etype (Def_Id));
2572 -- For a predefined container, the type of the loop variable is
2573 -- the Iterator_Element aspect of the container type.
2575 else
2576 declare
2577 Element : constant Entity_Id :=
2578 Find_Value_Of_Aspect
2579 (Typ, Aspect_Iterator_Element);
2580 Iterator : constant Entity_Id :=
2581 Find_Value_Of_Aspect
2582 (Typ, Aspect_Default_Iterator);
2583 Orig_Iter_Name : constant Node_Id :=
2584 Original_Node (Iter_Name);
2585 Cursor_Type : Entity_Id;
2587 begin
2588 if No (Element) then
2589 Error_Msg_NE ("cannot iterate over&", N, Typ);
2590 return;
2592 else
2593 Set_Etype (Def_Id, Entity (Element));
2594 Cursor_Type := Get_Cursor_Type (Typ);
2595 pragma Assert (Present (Cursor_Type));
2597 Check_Subtype_Definition (Etype (Def_Id));
2599 -- If the container has a variable indexing aspect, the
2600 -- element is a variable and is modifiable in the loop.
2602 if Has_Aspect (Typ, Aspect_Variable_Indexing) then
2603 Mutate_Ekind (Def_Id, E_Variable);
2604 Set_Is_Not_Self_Hidden (Def_Id);
2605 end if;
2607 -- If the container is a constant, iterating over it
2608 -- requires a Constant_Indexing operation.
2610 if not Is_Variable (Iter_Name)
2611 and then not Has_Aspect (Typ, Aspect_Constant_Indexing)
2612 then
2613 Error_Msg_N
2614 ("iteration over constant container require "
2615 & "constant_indexing aspect", N);
2617 -- The Iterate function may have an in_out parameter,
2618 -- and a constant container is thus illegal.
2620 elsif Present (Iterator)
2621 and then Ekind (Entity (Iterator)) = E_Function
2622 and then Ekind (First_Formal (Entity (Iterator))) /=
2623 E_In_Parameter
2624 and then not Is_Variable (Iter_Name)
2625 then
2626 Error_Msg_N ("variable container expected", N);
2627 end if;
2629 -- Detect a case where the iterator denotes a component
2630 -- of a mutable object which depends on a discriminant.
2631 -- Note that the iterator may denote a function call in
2632 -- qualified form, in which case this check should not
2633 -- be performed.
2635 if Nkind (Orig_Iter_Name) = N_Selected_Component
2636 and then
2637 Present (Entity (Selector_Name (Orig_Iter_Name)))
2638 and then
2639 Ekind (Entity (Selector_Name (Orig_Iter_Name))) in
2640 E_Component | E_Discriminant
2641 and then Is_Dependent_Component_Of_Mutable_Object
2642 (Orig_Iter_Name)
2643 then
2644 Error_Msg_N
2645 ("container cannot be a discriminant-dependent "
2646 & "component of a mutable object", N);
2648 elsif Depends_On_Mutably_Tagged_Ext_Comp
2649 (Orig_Iter_Name)
2650 then
2651 Error_Msg_N
2652 ("container cannot depend on a mutably tagged "
2653 & "component", N);
2654 end if;
2655 end if;
2656 end;
2657 end if;
2659 -- IN iterator, domain is a range, a call to Iterate function,
2660 -- or an object/actual parameter of an iterator type.
2662 else
2663 -- If the type of the name is class-wide and its root type is a
2664 -- derived type, the primitive operations (First, Next, etc.) are
2665 -- those inherited by its specific type. Calls to these primitives
2666 -- will be dispatching.
2668 if Is_Class_Wide_Type (Typ)
2669 and then Is_Derived_Type (Etype (Typ))
2670 then
2671 Typ := Etype (Typ);
2672 end if;
2674 -- For an iteration of the form IN, the name must denote an
2675 -- iterator, typically the result of a call to Iterate. Give a
2676 -- useful error message when the name is a container by itself.
2678 -- The type may be a formal container type, which has to have
2679 -- an Iterable aspect detailing the required primitives.
2681 if Is_Entity_Name (Original_Node (Name (N)))
2682 and then not Is_Iterator (Typ)
2683 then
2684 if Has_Aspect (Typ, Aspect_Iterable) then
2685 null;
2687 elsif not Has_Aspect (Typ, Aspect_Iterator_Element) then
2688 Error_Msg_NE
2689 ("cannot iterate over&", Name (N), Typ);
2690 else
2691 Error_Msg_N
2692 ("name must be an iterator, not a container", Name (N));
2693 end if;
2695 if Has_Aspect (Typ, Aspect_Iterable) then
2696 null;
2697 else
2698 Error_Msg_NE
2699 ("\to iterate directly over the elements of a container, "
2700 & "write `of &`", Name (N), Original_Node (Name (N)));
2702 -- No point in continuing analysis of iterator spec
2704 return;
2705 end if;
2706 end if;
2708 -- If the name is a call (typically prefixed) to some Iterate
2709 -- function, it has been rewritten as an object declaration.
2710 -- If that object is a selected component, verify that it is not
2711 -- a component of an unconstrained mutable object.
2713 if Nkind (Iter_Name) = N_Identifier
2714 or else (not Expander_Active and Comes_From_Source (Iter_Name))
2715 then
2716 declare
2717 Orig_Node : constant Node_Id := Original_Node (Iter_Name);
2718 Iter_Kind : constant Node_Kind := Nkind (Orig_Node);
2719 Obj : Node_Id;
2721 begin
2722 if Iter_Kind = N_Selected_Component then
2723 Obj := Prefix (Orig_Node);
2725 elsif Iter_Kind = N_Function_Call then
2726 Obj := First_Actual (Orig_Node);
2728 -- If neither, the name comes from source
2730 else
2731 Obj := Iter_Name;
2732 end if;
2734 if Nkind (Obj) = N_Selected_Component
2735 and then Is_Dependent_Component_Of_Mutable_Object (Obj)
2736 then
2737 Error_Msg_N
2738 ("container cannot be a discriminant-dependent "
2739 & "component of a mutable object", N);
2741 elsif Depends_On_Mutably_Tagged_Ext_Comp (Obj) then
2742 Error_Msg_N
2743 ("container cannot depend on a mutably tagged"
2744 & " component", N);
2745 end if;
2746 end;
2747 end if;
2749 -- The result type of Iterate function is the classwide type of
2750 -- the interface parent. We need the specific Cursor type defined
2751 -- in the container package. We obtain it by name for a predefined
2752 -- container, or through the Iterable aspect for a formal one.
2754 if Has_Aspect (Typ, Aspect_Iterable) then
2755 Set_Etype (Def_Id,
2756 Get_Cursor_Type
2757 (Parent (Find_Value_Of_Aspect (Typ, Aspect_Iterable)),
2758 Typ));
2760 else
2761 Set_Etype (Def_Id, Get_Cursor_Type (Typ));
2762 Check_Reverse_Iteration (Etype (Iter_Name));
2763 end if;
2765 end if;
2766 end if;
2768 -- Preanalyze the filter. Expansion will take place when enclosing
2769 -- loop is expanded.
2771 if Present (Iterator_Filter (N)) then
2772 Preanalyze_And_Resolve (Iterator_Filter (N), Standard_Boolean);
2773 end if;
2774 end Analyze_Iterator_Specification;
2776 -------------------
2777 -- Analyze_Label --
2778 -------------------
2780 -- Note: the semantic work required for analyzing labels (setting them as
2781 -- reachable) was done in a prepass through the statements in the block,
2782 -- so that forward gotos would be properly handled. See Analyze_Statements
2783 -- for further details. The only processing required here is to deal with
2784 -- optimizations that depend on an assumption of sequential control flow,
2785 -- since of course the occurrence of a label breaks this assumption.
2787 procedure Analyze_Label (N : Node_Id) is
2788 pragma Warnings (Off, N);
2789 begin
2790 Kill_Current_Values;
2791 end Analyze_Label;
2793 ------------------------------------------
2794 -- Analyze_Loop_Parameter_Specification --
2795 ------------------------------------------
2797 procedure Analyze_Loop_Parameter_Specification (N : Node_Id) is
2798 Loop_Nod : constant Node_Id := Parent (Parent (N));
2800 procedure Check_Controlled_Array_Attribute (DS : Node_Id);
2801 -- If the bounds are given by a 'Range reference on a function call
2802 -- that returns a controlled array, introduce an explicit declaration
2803 -- to capture the bounds, so that the function result can be finalized
2804 -- in timely fashion.
2806 procedure Check_Predicate_Use (T : Entity_Id);
2807 -- Diagnose Attempt to iterate through non-static predicate. Note that
2808 -- a type with inherited predicates may have both static and dynamic
2809 -- forms. In this case it is not sufficient to check the static
2810 -- predicate function only, look for a dynamic predicate aspect as well.
2812 procedure Process_Bounds (R : Node_Id);
2813 -- If the iteration is given by a range, create temporaries and
2814 -- assignment statements block to capture the bounds and perform
2815 -- required finalization actions in case a bound includes a function
2816 -- call that uses the temporary stack. We first preanalyze a copy of
2817 -- the range in order to determine the expected type, and analyze and
2818 -- resolve the original bounds.
2820 --------------------------------------
2821 -- Check_Controlled_Array_Attribute --
2822 --------------------------------------
2824 procedure Check_Controlled_Array_Attribute (DS : Node_Id) is
2825 begin
2826 if Nkind (DS) = N_Attribute_Reference
2827 and then Is_Entity_Name (Prefix (DS))
2828 and then Ekind (Entity (Prefix (DS))) = E_Function
2829 and then Is_Array_Type (Etype (Entity (Prefix (DS))))
2830 and then
2831 Is_Controlled (Component_Type (Etype (Entity (Prefix (DS)))))
2832 and then Expander_Active
2833 then
2834 declare
2835 Loc : constant Source_Ptr := Sloc (N);
2836 Arr : constant Entity_Id := Etype (Entity (Prefix (DS)));
2837 Indx : constant Entity_Id :=
2838 Base_Type (Etype (First_Index (Arr)));
2839 Subt : constant Entity_Id := Make_Temporary (Loc, 'S');
2840 Decl : Node_Id;
2842 begin
2843 Decl :=
2844 Make_Subtype_Declaration (Loc,
2845 Defining_Identifier => Subt,
2846 Subtype_Indication =>
2847 Make_Subtype_Indication (Loc,
2848 Subtype_Mark => New_Occurrence_Of (Indx, Loc),
2849 Constraint =>
2850 Make_Range_Constraint (Loc, Relocate_Node (DS))));
2851 Insert_Before (Loop_Nod, Decl);
2852 Analyze (Decl);
2854 Rewrite (DS,
2855 Make_Attribute_Reference (Loc,
2856 Prefix => New_Occurrence_Of (Subt, Loc),
2857 Attribute_Name => Attribute_Name (DS)));
2859 Analyze (DS);
2860 end;
2861 end if;
2862 end Check_Controlled_Array_Attribute;
2864 -------------------------
2865 -- Check_Predicate_Use --
2866 -------------------------
2868 procedure Check_Predicate_Use (T : Entity_Id) is
2869 begin
2870 -- A predicated subtype is illegal in loops and related constructs
2871 -- if the predicate is not static, or if it is a non-static subtype
2872 -- of a statically predicated subtype.
2874 if Is_Discrete_Type (T)
2875 and then Has_Predicates (T)
2876 and then (not Has_Static_Predicate (T)
2877 or else not Is_Static_Subtype (T)
2878 or else Has_Dynamic_Predicate_Aspect (T)
2879 or else Has_Ghost_Predicate_Aspect (T))
2880 then
2881 -- Seems a confusing message for the case of a static predicate
2882 -- with a non-static subtype???
2884 Bad_Predicated_Subtype_Use
2885 ("cannot use subtype& with non-static predicate for loop "
2886 & "iteration", Discrete_Subtype_Definition (N),
2887 T, Suggest_Static => True);
2889 elsif Inside_A_Generic
2890 and then Is_Generic_Formal (T)
2891 and then Is_Discrete_Type (T)
2892 then
2893 Set_No_Dynamic_Predicate_On_Actual (T);
2894 end if;
2895 end Check_Predicate_Use;
2897 --------------------
2898 -- Process_Bounds --
2899 --------------------
2901 procedure Process_Bounds (R : Node_Id) is
2902 Loc : constant Source_Ptr := Sloc (N);
2904 function One_Bound
2905 (Original_Bound : Node_Id;
2906 Analyzed_Bound : Node_Id;
2907 Typ : Entity_Id) return Node_Id;
2908 -- Capture value of bound and return captured value
2910 ---------------
2911 -- One_Bound --
2912 ---------------
2914 function One_Bound
2915 (Original_Bound : Node_Id;
2916 Analyzed_Bound : Node_Id;
2917 Typ : Entity_Id) return Node_Id
2919 Assign : Node_Id;
2920 Decl : Node_Id;
2921 Id : Entity_Id;
2923 begin
2924 -- If the bound is a constant or an object, no need for a separate
2925 -- declaration. If the bound is the result of previous expansion
2926 -- it is already analyzed and should not be modified. Note that
2927 -- the Bound will be resolved later, if needed, as part of the
2928 -- call to Make_Index (literal bounds may need to be resolved to
2929 -- type Integer).
2931 if Analyzed (Original_Bound) then
2932 return Original_Bound;
2934 elsif Nkind (Analyzed_Bound) in
2935 N_Integer_Literal | N_Character_Literal
2936 or else Is_Entity_Name (Analyzed_Bound)
2937 then
2938 Analyze_And_Resolve (Original_Bound, Typ);
2939 return Original_Bound;
2941 elsif Inside_Class_Condition_Preanalysis then
2942 Analyze_And_Resolve (Original_Bound, Typ);
2943 return Original_Bound;
2944 end if;
2946 -- Normally, the best approach is simply to generate a constant
2947 -- declaration that captures the bound. However, there is a nasty
2948 -- case where this is wrong. If the bound is complex, and has a
2949 -- possible use of the secondary stack, we need to generate a
2950 -- separate assignment statement to ensure the creation of a block
2951 -- which will release the secondary stack.
2953 -- We prefer the constant declaration, since it leaves us with a
2954 -- proper trace of the value, useful in optimizations that get rid
2955 -- of junk range checks.
2957 if not Has_Sec_Stack_Call (Analyzed_Bound) then
2958 Analyze_And_Resolve (Original_Bound, Typ);
2960 -- Ensure that the bound is valid. This check should not be
2961 -- generated when the range belongs to a quantified expression
2962 -- as the construct is still not expanded into its final form.
2964 if Nkind (Parent (R)) /= N_Loop_Parameter_Specification
2965 or else Nkind (Parent (Parent (R))) /= N_Quantified_Expression
2966 then
2967 Ensure_Valid (Original_Bound);
2968 end if;
2970 Force_Evaluation (Original_Bound);
2971 return Original_Bound;
2972 end if;
2974 Id := Make_Temporary (Loc, 'R', Original_Bound);
2976 -- Here we make a declaration with a separate assignment
2977 -- statement, and insert before loop header.
2979 Decl :=
2980 Make_Object_Declaration (Loc,
2981 Defining_Identifier => Id,
2982 Object_Definition => New_Occurrence_Of (Typ, Loc));
2984 Assign :=
2985 Make_Assignment_Statement (Loc,
2986 Name => New_Occurrence_Of (Id, Loc),
2987 Expression => Relocate_Node (Original_Bound));
2989 Insert_Actions (Loop_Nod, New_List (Decl, Assign));
2991 -- Now that this temporary variable is initialized we decorate it
2992 -- as safe-to-reevaluate to inform to the backend that no further
2993 -- asignment will be issued and hence it can be handled as side
2994 -- effect free. Note that this decoration must be done when the
2995 -- assignment has been analyzed because otherwise it will be
2996 -- rejected (see Analyze_Assignment).
2998 Set_Is_Safe_To_Reevaluate (Id);
3000 Rewrite (Original_Bound, New_Occurrence_Of (Id, Loc));
3002 if Nkind (Assign) = N_Assignment_Statement then
3003 return Expression (Assign);
3004 else
3005 return Original_Bound;
3006 end if;
3007 end One_Bound;
3009 Hi : constant Node_Id := High_Bound (R);
3010 Lo : constant Node_Id := Low_Bound (R);
3011 R_Copy : constant Node_Id := New_Copy_Tree (R);
3012 New_Hi : Node_Id;
3013 New_Lo : Node_Id;
3014 Typ : Entity_Id;
3016 -- Start of processing for Process_Bounds
3018 begin
3019 Set_Parent (R_Copy, Parent (R));
3020 Preanalyze_Range (R_Copy);
3021 Typ := Etype (R_Copy);
3023 -- If the type of the discrete range is Universal_Integer, then the
3024 -- bound's type must be resolved to Integer, and any object used to
3025 -- hold the bound must also have type Integer, unless the literal
3026 -- bounds are constant-folded expressions with a user-defined type.
3028 if Typ = Universal_Integer then
3029 if Nkind (Lo) = N_Integer_Literal
3030 and then Present (Etype (Lo))
3031 and then Scope (Etype (Lo)) /= Standard_Standard
3032 then
3033 Typ := Etype (Lo);
3035 elsif Nkind (Hi) = N_Integer_Literal
3036 and then Present (Etype (Hi))
3037 and then Scope (Etype (Hi)) /= Standard_Standard
3038 then
3039 Typ := Etype (Hi);
3041 else
3042 Typ := Standard_Integer;
3043 end if;
3044 end if;
3046 Set_Etype (R, Typ);
3048 New_Lo := One_Bound (Lo, Low_Bound (R_Copy), Typ);
3049 New_Hi := One_Bound (Hi, High_Bound (R_Copy), Typ);
3051 -- Propagate staticness to loop range itself, in case the
3052 -- corresponding subtype is static.
3054 if New_Lo /= Lo and then Is_OK_Static_Expression (New_Lo) then
3055 Rewrite (Low_Bound (R), New_Copy (New_Lo));
3056 end if;
3058 if New_Hi /= Hi and then Is_OK_Static_Expression (New_Hi) then
3059 Rewrite (High_Bound (R), New_Copy (New_Hi));
3060 end if;
3061 end Process_Bounds;
3063 -- Local variables
3065 DS : constant Node_Id := Discrete_Subtype_Definition (N);
3066 Id : constant Entity_Id := Defining_Identifier (N);
3068 DS_Copy : Node_Id;
3070 -- Start of processing for Analyze_Loop_Parameter_Specification
3072 begin
3073 Enter_Name (Id);
3075 -- We always consider the loop variable to be referenced, since the loop
3076 -- may be used just for counting purposes.
3078 Generate_Reference (Id, N, ' ');
3080 -- Check for the case of loop variable hiding a local variable (used
3081 -- later on to give a nice warning if the hidden variable is never
3082 -- assigned).
3084 declare
3085 H : constant Entity_Id := Homonym (Id);
3086 begin
3087 if Present (H)
3088 and then Ekind (H) = E_Variable
3089 and then Is_Discrete_Type (Etype (H))
3090 and then Enclosing_Dynamic_Scope (H) = Enclosing_Dynamic_Scope (Id)
3091 then
3092 Set_Hiding_Loop_Variable (H, Id);
3093 end if;
3094 end;
3096 -- Analyze the subtype definition and create temporaries for the bounds.
3097 -- Do not evaluate the range when preanalyzing a quantified expression
3098 -- because bounds expressed as function calls with side effects will be
3099 -- incorrectly replicated.
3101 if Nkind (DS) = N_Range
3102 and then Expander_Active
3103 and then Nkind (Parent (N)) /= N_Quantified_Expression
3104 then
3105 Process_Bounds (DS);
3107 -- Either the expander not active or the range of iteration is a subtype
3108 -- indication, an entity, or a function call that yields an aggregate or
3109 -- a container.
3111 else
3112 DS_Copy := New_Copy_Tree (DS);
3113 Set_Parent (DS_Copy, Parent (DS));
3114 Preanalyze_Range (DS_Copy);
3116 -- Ada 2012: If the domain of iteration is:
3118 -- a) a function call,
3119 -- b) an identifier that is not a type,
3120 -- c) an attribute reference 'Old (within a postcondition),
3121 -- d) an unchecked conversion or a qualified expression with
3122 -- the proper iterator type.
3124 -- then it is an iteration over a container. It was classified as
3125 -- a loop specification by the parser, and must be rewritten now
3126 -- to activate container iteration. The last case will occur within
3127 -- an expanded inlined call, where the expansion wraps an actual in
3128 -- an unchecked conversion when needed. The expression of the
3129 -- conversion is always an object.
3131 if Nkind (DS_Copy) = N_Function_Call
3133 or else (Is_Entity_Name (DS_Copy)
3134 and then not Is_Type (Entity (DS_Copy)))
3136 or else (Nkind (DS_Copy) = N_Attribute_Reference
3137 and then Attribute_Name (DS_Copy) in
3138 Name_Loop_Entry | Name_Old)
3140 or else Has_Aspect (Etype (DS_Copy), Aspect_Iterable)
3142 or else Nkind (DS_Copy) = N_Unchecked_Type_Conversion
3143 or else (Nkind (DS_Copy) = N_Qualified_Expression
3144 and then Is_Iterator (Etype (DS_Copy)))
3145 then
3146 -- This is an iterator specification. Rewrite it as such and
3147 -- analyze it to capture function calls that may require
3148 -- finalization actions.
3150 declare
3151 I_Spec : constant Node_Id :=
3152 Make_Iterator_Specification (Sloc (N),
3153 Defining_Identifier => Relocate_Node (Id),
3154 Name => DS_Copy,
3155 Subtype_Indication => Empty,
3156 Reverse_Present => Reverse_Present (N));
3157 Scheme : constant Node_Id := Parent (N);
3159 begin
3160 Set_Iterator_Specification (Scheme, I_Spec);
3161 Set_Loop_Parameter_Specification (Scheme, Empty);
3162 Set_Iterator_Filter (I_Spec,
3163 Relocate_Node (Iterator_Filter (N)));
3165 Analyze_Iterator_Specification (I_Spec);
3167 -- In a generic context, analyze the original domain of
3168 -- iteration, for name capture.
3170 if not Expander_Active then
3171 Analyze (DS);
3172 end if;
3174 -- Set kind of loop parameter, which may be used in the
3175 -- subsequent analysis of the condition in a quantified
3176 -- expression.
3178 Mutate_Ekind (Id, E_Loop_Parameter);
3179 return;
3180 end;
3182 -- Domain of iteration is not a function call, and is side-effect
3183 -- free.
3185 else
3186 -- A quantified expression that appears in a pre/post condition
3187 -- is preanalyzed several times. If the range is given by an
3188 -- attribute reference it is rewritten as a range, and this is
3189 -- done even with expansion disabled. If the type is already set
3190 -- do not reanalyze, because a range with static bounds may be
3191 -- typed Integer by default.
3193 if Nkind (Parent (N)) = N_Quantified_Expression
3194 and then Present (Etype (DS))
3195 then
3196 null;
3197 else
3198 Analyze (DS);
3199 end if;
3200 end if;
3201 end if;
3203 if DS = Error then
3204 return;
3205 end if;
3207 -- Some additional checks if we are iterating through a type
3209 if Is_Entity_Name (DS)
3210 and then Present (Entity (DS))
3211 and then Is_Type (Entity (DS))
3212 then
3213 -- The subtype indication may denote the completion of an incomplete
3214 -- type declaration.
3216 if Ekind (Entity (DS)) = E_Incomplete_Type then
3217 Set_Entity (DS, Get_Full_View (Entity (DS)));
3218 Set_Etype (DS, Entity (DS));
3219 end if;
3221 Check_Predicate_Use (Entity (DS));
3222 end if;
3224 -- Error if not discrete type
3226 if not Is_Discrete_Type (Etype (DS)) then
3227 Wrong_Type (DS, Any_Discrete);
3228 Set_Etype (DS, Any_Type);
3229 end if;
3231 Check_Controlled_Array_Attribute (DS);
3233 if Nkind (DS) = N_Subtype_Indication then
3234 Check_Predicate_Use (Entity (Subtype_Mark (DS)));
3235 end if;
3237 if Nkind (DS) not in N_Raise_xxx_Error then
3238 Make_Index (DS, N);
3239 end if;
3241 Mutate_Ekind (Id, E_Loop_Parameter);
3242 Set_Is_Not_Self_Hidden (Id);
3244 -- A quantified expression which appears in a pre- or post-condition may
3245 -- be analyzed multiple times. The analysis of the range creates several
3246 -- itypes which reside in different scopes depending on whether the pre-
3247 -- or post-condition has been expanded. Update the type of the loop
3248 -- variable to reflect the proper itype at each stage of analysis.
3250 -- Loop_Nod might not be present when we are preanalyzing a class-wide
3251 -- pre/postcondition since preanalysis occurs in a place unrelated to
3252 -- the actual code and the quantified expression may be the outermost
3253 -- expression of the class-wide condition.
3255 if No (Etype (Id))
3256 or else Etype (Id) = Any_Type
3257 or else
3258 (Present (Etype (Id))
3259 and then Is_Itype (Etype (Id))
3260 and then Present (Loop_Nod)
3261 and then Nkind (Parent (Loop_Nod)) = N_Expression_With_Actions
3262 and then Nkind (Original_Node (Parent (Loop_Nod))) =
3263 N_Quantified_Expression)
3264 then
3265 Set_Etype (Id, Etype (DS));
3266 end if;
3268 -- Treat a range as an implicit reference to the type, to inhibit
3269 -- spurious warnings.
3271 Generate_Reference (Base_Type (Etype (DS)), N, ' ');
3272 Set_Is_Known_Valid (Id, True);
3274 -- The loop is not a declarative part, so the loop variable must be
3275 -- frozen explicitly. Do not freeze while preanalyzing a quantified
3276 -- expression because the freeze node will not be inserted into the
3277 -- tree due to flag Is_Spec_Expression being set.
3279 if Nkind (Parent (N)) /= N_Quantified_Expression then
3280 declare
3281 Flist : constant List_Id := Freeze_Entity (Id, N);
3282 begin
3283 Insert_Actions (N, Flist);
3284 end;
3285 end if;
3287 -- Case where we have a range or a subtype, get type bounds
3289 if Nkind (DS) in N_Range | N_Subtype_Indication
3290 and then not Error_Posted (DS)
3291 and then Etype (DS) /= Any_Type
3292 and then Is_Discrete_Type (Etype (DS))
3293 then
3294 declare
3295 L : Node_Id;
3296 H : Node_Id;
3297 Null_Range : Boolean := False;
3299 begin
3300 if Nkind (DS) = N_Range then
3301 L := Low_Bound (DS);
3302 H := High_Bound (DS);
3303 else
3304 L :=
3305 Type_Low_Bound (Underlying_Type (Etype (Subtype_Mark (DS))));
3306 H :=
3307 Type_High_Bound (Underlying_Type (Etype (Subtype_Mark (DS))));
3308 end if;
3310 -- Check for null or possibly null range and issue warning. We
3311 -- suppress such messages in generic templates and instances,
3312 -- because in practice they tend to be dubious in these cases. The
3313 -- check applies as well to rewritten array element loops where a
3314 -- null range may be detected statically.
3316 if Compile_Time_Compare (L, H, Assume_Valid => True) = GT then
3317 if Compile_Time_Compare (L, H, Assume_Valid => False) = GT then
3318 -- Since we know the range of the loop is always null,
3319 -- set the appropriate flag to remove the loop entirely
3320 -- during expansion.
3322 Set_Is_Null_Loop (Loop_Nod);
3323 Null_Range := True;
3324 end if;
3326 -- Suppress the warning if inside a generic template or
3327 -- instance, since in practice they tend to be dubious in these
3328 -- cases since they can result from intended parameterization.
3330 if not Inside_A_Generic and then not In_Instance then
3332 -- Specialize msg if invalid values could make the loop
3333 -- non-null after all.
3335 if Null_Range then
3336 if Comes_From_Source (N) then
3337 Error_Msg_N
3338 ("??loop range is null, loop will not execute", DS);
3339 end if;
3341 -- Here is where the loop could execute because of
3342 -- invalid values, so issue appropriate message.
3344 elsif Comes_From_Source (N) then
3345 Error_Msg_N
3346 ("??loop range may be null, loop may not execute",
3347 DS);
3348 Error_Msg_N
3349 ("??can only execute if invalid values are present",
3350 DS);
3351 end if;
3352 end if;
3354 -- In either case, suppress warnings in the body of the loop,
3355 -- since it is likely that these warnings will be inappropriate
3356 -- if the loop never actually executes, which is likely.
3358 Set_Suppress_Loop_Warnings (Loop_Nod);
3360 -- The other case for a warning is a reverse loop where the
3361 -- upper bound is the integer literal zero or one, and the
3362 -- lower bound may exceed this value.
3364 -- For example, we have
3366 -- for J in reverse N .. 1 loop
3368 -- In practice, this is very likely to be a case of reversing
3369 -- the bounds incorrectly in the range.
3371 elsif Reverse_Present (N)
3372 and then Nkind (Original_Node (H)) = N_Integer_Literal
3373 and then
3374 (Intval (Original_Node (H)) = Uint_0
3375 or else
3376 Intval (Original_Node (H)) = Uint_1)
3377 then
3378 -- Lower bound may in fact be known and known not to exceed
3379 -- upper bound (e.g. reverse 0 .. 1) and that's OK.
3381 if Compile_Time_Known_Value (L)
3382 and then Expr_Value (L) <= Expr_Value (H)
3383 then
3384 null;
3386 -- Otherwise warning is warranted
3388 else
3389 Error_Msg_N ("??loop range may be null", DS);
3390 Error_Msg_N ("\??bounds may be wrong way round", DS);
3391 end if;
3392 end if;
3394 -- Check if either bound is known to be outside the range of the
3395 -- loop parameter type, this is e.g. the case of a loop from
3396 -- 20..X where the type is 1..19.
3398 -- Such a loop is dubious since either it raises CE or it executes
3399 -- zero times, and that cannot be useful!
3401 if Etype (DS) /= Any_Type
3402 and then not Error_Posted (DS)
3403 and then Nkind (DS) = N_Subtype_Indication
3404 and then Nkind (Constraint (DS)) = N_Range_Constraint
3405 then
3406 declare
3407 LLo : constant Node_Id :=
3408 Low_Bound (Range_Expression (Constraint (DS)));
3409 LHi : constant Node_Id :=
3410 High_Bound (Range_Expression (Constraint (DS)));
3412 Bad_Bound : Node_Id := Empty;
3413 -- Suspicious loop bound
3415 begin
3416 -- At this stage L, H are the bounds of the type, and LLo
3417 -- Lhi are the low bound and high bound of the loop.
3419 if Compile_Time_Compare (LLo, L, Assume_Valid => True) = LT
3420 or else
3421 Compile_Time_Compare (LLo, H, Assume_Valid => True) = GT
3422 then
3423 Bad_Bound := LLo;
3424 end if;
3426 if Compile_Time_Compare (LHi, L, Assume_Valid => True) = LT
3427 or else
3428 Compile_Time_Compare (LHi, H, Assume_Valid => True) = GT
3429 then
3430 Bad_Bound := LHi;
3431 end if;
3433 if Present (Bad_Bound) then
3434 Error_Msg_N
3435 ("suspicious loop bound out of range of "
3436 & "loop subtype??", Bad_Bound);
3437 Error_Msg_N
3438 ("\loop executes zero times or raises "
3439 & "Constraint_Error??", Bad_Bound);
3440 end if;
3442 if Compile_Time_Compare (LLo, LHi, Assume_Valid => False)
3443 = GT
3444 then
3445 Error_Msg_N ("??constrained range is null",
3446 Constraint (DS));
3448 -- Additional constraints on modular types can be
3449 -- confusing, add more information.
3451 if Ekind (Etype (DS)) = E_Modular_Integer_Subtype then
3452 Error_Msg_Uint_1 := Intval (LLo);
3453 Error_Msg_Uint_2 := Intval (LHi);
3454 Error_Msg_NE ("\iterator has modular type &, " &
3455 "so the loop has bounds ^ ..^",
3456 Constraint (DS),
3457 Subtype_Mark (DS));
3458 end if;
3460 Set_Is_Null_Loop (Loop_Nod);
3461 Null_Range := True;
3463 -- Suppress other warnings about the body of the loop, as
3464 -- it will never execute.
3465 Set_Suppress_Loop_Warnings (Loop_Nod);
3466 end if;
3467 end;
3468 end if;
3470 -- This declare block is about warnings, if we get an exception while
3471 -- testing for warnings, we simply abandon the attempt silently. This
3472 -- most likely occurs as the result of a previous error, but might
3473 -- just be an obscure case we have missed. In either case, not giving
3474 -- the warning is perfectly acceptable.
3476 exception
3477 when others =>
3478 -- With debug flag K we will get an exception unless an error
3479 -- has already occurred (useful for debugging).
3481 if Debug_Flag_K then
3482 Check_Error_Detected;
3483 end if;
3484 end;
3485 end if;
3487 -- Preanalyze the filter. Expansion will take place when enclosing
3488 -- loop is expanded.
3490 if Present (Iterator_Filter (N)) then
3491 Preanalyze_And_Resolve (Iterator_Filter (N), Standard_Boolean);
3492 end if;
3493 end Analyze_Loop_Parameter_Specification;
3495 ----------------------------
3496 -- Analyze_Loop_Statement --
3497 ----------------------------
3499 procedure Analyze_Loop_Statement (N : Node_Id) is
3501 -- The following exception is raised by routine Prepare_Loop_Statement
3502 -- to avoid further analysis of a transformed loop.
3504 procedure Prepare_Loop_Statement
3505 (Iter : Node_Id;
3506 Stop_Processing : out Boolean);
3507 -- Determine whether loop statement N with iteration scheme Iter must be
3508 -- transformed prior to analysis, and if so, perform it.
3509 -- If Stop_Processing is set to True, should stop further processing.
3511 ----------------------------
3512 -- Prepare_Loop_Statement --
3513 ----------------------------
3515 procedure Prepare_Loop_Statement
3516 (Iter : Node_Id;
3517 Stop_Processing : out Boolean)
3519 function Has_Sec_Stack_Default_Iterator
3520 (Cont_Typ : Entity_Id) return Boolean;
3521 pragma Inline (Has_Sec_Stack_Default_Iterator);
3522 -- Determine whether container type Cont_Typ has a default iterator
3523 -- that requires secondary stack management.
3525 function Is_Sec_Stack_Iteration_Primitive
3526 (Cont_Typ : Entity_Id;
3527 Iter_Prim_Nam : Name_Id) return Boolean;
3528 pragma Inline (Is_Sec_Stack_Iteration_Primitive);
3529 -- Determine whether container type Cont_Typ has an iteration routine
3530 -- described by its name Iter_Prim_Nam that requires secondary stack
3531 -- management.
3533 function Is_Wrapped_In_Block (Stmt : Node_Id) return Boolean;
3534 pragma Inline (Is_Wrapped_In_Block);
3535 -- Determine whether arbitrary statement Stmt is the sole statement
3536 -- wrapped within some block, excluding pragmas.
3538 procedure Prepare_Iterator_Loop
3539 (Iter_Spec : Node_Id;
3540 Stop_Processing : out Boolean);
3541 pragma Inline (Prepare_Iterator_Loop);
3542 -- Prepare an iterator loop with iteration specification Iter_Spec
3543 -- for transformation if needed.
3544 -- If Stop_Processing is set to True, should stop further processing.
3546 procedure Prepare_Param_Spec_Loop
3547 (Param_Spec : Node_Id;
3548 Stop_Processing : out Boolean);
3549 pragma Inline (Prepare_Param_Spec_Loop);
3550 -- Prepare a discrete loop with parameter specification Param_Spec
3551 -- for transformation if needed.
3552 -- If Stop_Processing is set to True, should stop further processing.
3554 procedure Wrap_Loop_Statement (Manage_Sec_Stack : Boolean);
3555 pragma Inline (Wrap_Loop_Statement);
3556 -- Wrap loop statement N within a block. Flag Manage_Sec_Stack must
3557 -- be set when the block must mark and release the secondary stack.
3558 -- Should stop further processing after calling this procedure.
3560 ------------------------------------
3561 -- Has_Sec_Stack_Default_Iterator --
3562 ------------------------------------
3564 function Has_Sec_Stack_Default_Iterator
3565 (Cont_Typ : Entity_Id) return Boolean
3567 Def_Iter : constant Node_Id :=
3568 Find_Value_Of_Aspect
3569 (Cont_Typ, Aspect_Default_Iterator);
3570 begin
3571 return
3572 Present (Def_Iter)
3573 and then Present (Etype (Def_Iter))
3574 and then Requires_Transient_Scope (Etype (Def_Iter));
3575 end Has_Sec_Stack_Default_Iterator;
3577 --------------------------------------
3578 -- Is_Sec_Stack_Iteration_Primitive --
3579 --------------------------------------
3581 function Is_Sec_Stack_Iteration_Primitive
3582 (Cont_Typ : Entity_Id;
3583 Iter_Prim_Nam : Name_Id) return Boolean
3585 Iter_Prim : constant Entity_Id :=
3586 Get_Iterable_Type_Primitive
3587 (Cont_Typ, Iter_Prim_Nam);
3588 begin
3589 return
3590 Present (Iter_Prim)
3591 and then Requires_Transient_Scope (Etype (Iter_Prim));
3592 end Is_Sec_Stack_Iteration_Primitive;
3594 -------------------------
3595 -- Is_Wrapped_In_Block --
3596 -------------------------
3598 function Is_Wrapped_In_Block (Stmt : Node_Id) return Boolean is
3599 Blk_HSS : Node_Id;
3600 Blk_Id : Entity_Id;
3601 Blk_Stmt : Node_Id;
3603 begin
3604 Blk_Id := Current_Scope;
3606 -- The current context is a block. Inspect the statements of the
3607 -- block to determine whether it wraps Stmt.
3609 if Ekind (Blk_Id) = E_Block
3610 and then Present (Block_Node (Blk_Id))
3611 then
3612 Blk_HSS :=
3613 Handled_Statement_Sequence (Parent (Block_Node (Blk_Id)));
3615 -- Skip leading pragmas introduced for invariant and predicate
3616 -- checks.
3618 Blk_Stmt := First (Statements (Blk_HSS));
3619 while Present (Blk_Stmt)
3620 and then Nkind (Blk_Stmt) = N_Pragma
3621 loop
3622 Next (Blk_Stmt);
3623 end loop;
3625 return Blk_Stmt = Stmt and then No (Next (Blk_Stmt));
3626 end if;
3628 return False;
3629 end Is_Wrapped_In_Block;
3631 ---------------------------
3632 -- Prepare_Iterator_Loop --
3633 ---------------------------
3635 procedure Prepare_Iterator_Loop
3636 (Iter_Spec : Node_Id;
3637 Stop_Processing : out Boolean)
3639 Cont_Typ : Entity_Id;
3640 Nam : Node_Id;
3641 Nam_Copy : Node_Id;
3643 begin
3644 Stop_Processing := False;
3646 -- The iterator specification has syntactic errors. Transform the
3647 -- loop into an infinite loop in order to safely perform at least
3648 -- some minor analysis. This check must come first.
3650 if Error_Posted (Iter_Spec) then
3651 Set_Iteration_Scheme (N, Empty);
3652 Analyze (N);
3653 Stop_Processing := True;
3655 -- Nothing to do when the loop is already wrapped in a block
3657 elsif Is_Wrapped_In_Block (N) then
3658 null;
3660 -- Otherwise the iterator loop traverses an array or a container
3661 -- and appears in the form
3663 -- for Def_Id in [reverse] Iterator_Name loop
3664 -- for Def_Id [: Subtyp_Indic] of [reverse] Iterable_Name loop
3666 else
3667 -- Prepare a copy of the iterated name for preanalysis. The
3668 -- copy is semi inserted into the tree by setting its Parent
3669 -- pointer.
3671 Nam := Name (Iter_Spec);
3672 Nam_Copy := New_Copy_Tree (Nam);
3673 Set_Parent (Nam_Copy, Parent (Nam));
3675 -- Determine what the loop is iterating on
3677 Preanalyze_Range (Nam_Copy);
3678 Cont_Typ := Etype (Nam_Copy);
3680 -- The iterator loop is traversing an array. This case does not
3681 -- require any transformation, unless the name contains a call
3682 -- that returns on the secondary stack since we need to release
3683 -- the space allocated there.
3685 if Is_Array_Type (Cont_Typ)
3686 and then not Has_Sec_Stack_Call (Nam_Copy)
3687 then
3688 null;
3690 -- Otherwise unconditionally wrap the loop statement within
3691 -- a block. The expansion of iterator loops may relocate the
3692 -- iterator outside the loop, thus "leaking" its entity into
3693 -- the enclosing scope. Wrapping the loop statement allows
3694 -- for multiple iterator loops using the same iterator name
3695 -- to coexist within the same scope.
3697 -- The block must manage the secondary stack when the iterator
3698 -- loop is traversing a container using either
3700 -- * A default iterator obtained on the secondary stack
3702 -- * Call to Iterate where the iterator is returned on the
3703 -- secondary stack.
3705 -- * Combination of First, Next, and Has_Element where the
3706 -- first two return a cursor on the secondary stack.
3708 else
3709 Wrap_Loop_Statement
3710 (Manage_Sec_Stack =>
3711 Has_Sec_Stack_Default_Iterator (Cont_Typ)
3712 or else Has_Sec_Stack_Call (Nam_Copy)
3713 or else Is_Sec_Stack_Iteration_Primitive
3714 (Cont_Typ, Name_First)
3715 or else Is_Sec_Stack_Iteration_Primitive
3716 (Cont_Typ, Name_Next));
3717 Stop_Processing := True;
3718 end if;
3719 end if;
3720 end Prepare_Iterator_Loop;
3722 -----------------------------
3723 -- Prepare_Param_Spec_Loop --
3724 -----------------------------
3726 procedure Prepare_Param_Spec_Loop
3727 (Param_Spec : Node_Id;
3728 Stop_Processing : out Boolean)
3730 High : Node_Id;
3731 Low : Node_Id;
3732 Rng : Node_Id;
3733 Rng_Copy : Node_Id;
3734 Rng_Typ : Entity_Id;
3736 begin
3737 Stop_Processing := False;
3738 Rng := Discrete_Subtype_Definition (Param_Spec);
3740 -- Nothing to do when the loop is already wrapped in a block
3742 if Is_Wrapped_In_Block (N) then
3743 null;
3745 -- The parameter specification appears in the form
3747 -- for Def_Id in Subtype_Mark Constraint loop
3749 elsif Nkind (Rng) = N_Subtype_Indication
3750 and then Nkind (Range_Expression (Constraint (Rng))) = N_Range
3751 then
3752 Rng := Range_Expression (Constraint (Rng));
3754 -- Preanalyze the bounds of the range constraint, setting
3755 -- parent fields to associate the copied bounds with the range,
3756 -- allowing proper tree climbing during preanalysis.
3758 Low := New_Copy_Tree (Low_Bound (Rng));
3759 High := New_Copy_Tree (High_Bound (Rng));
3761 Set_Parent (Low, Rng);
3762 Set_Parent (High, Rng);
3764 Preanalyze (Low);
3765 Preanalyze (High);
3767 -- The bounds contain at least one function call that returns
3768 -- on the secondary stack. Note that the loop must be wrapped
3769 -- only when such a call exists.
3771 if Has_Sec_Stack_Call (Low) or else Has_Sec_Stack_Call (High)
3772 then
3773 Wrap_Loop_Statement (Manage_Sec_Stack => True);
3774 Stop_Processing := True;
3775 end if;
3777 -- Otherwise the parameter specification appears in the form
3779 -- for Def_Id in Range loop
3781 else
3782 -- Prepare a copy of the discrete range for preanalysis. The
3783 -- copy is semi inserted into the tree by setting its Parent
3784 -- pointer.
3786 Rng_Copy := New_Copy_Tree (Rng);
3787 Set_Parent (Rng_Copy, Parent (Rng));
3789 -- Determine what the loop is iterating on
3791 Preanalyze_Range (Rng_Copy);
3792 Rng_Typ := Etype (Rng_Copy);
3794 -- Wrap the loop statement within a block in order to manage
3795 -- the secondary stack when the discrete range is
3797 -- * Either a Forward_Iterator or a Reverse_Iterator
3799 -- * Function call whose return type requires finalization
3800 -- actions.
3802 -- ??? it is unclear why using Has_Sec_Stack_Call directly on
3803 -- the discrete range causes the freeze node of an itype to be
3804 -- in the wrong scope in complex assertion expressions.
3806 if Is_Iterator (Rng_Typ)
3807 or else (Nkind (Rng_Copy) = N_Function_Call
3808 and then Needs_Finalization (Rng_Typ))
3809 then
3810 Wrap_Loop_Statement (Manage_Sec_Stack => True);
3811 Stop_Processing := True;
3812 end if;
3813 end if;
3814 end Prepare_Param_Spec_Loop;
3816 -------------------------
3817 -- Wrap_Loop_Statement --
3818 -------------------------
3820 procedure Wrap_Loop_Statement (Manage_Sec_Stack : Boolean) is
3821 Loc : constant Source_Ptr := Sloc (N);
3823 Blk : Node_Id;
3824 Blk_Id : Entity_Id;
3826 begin
3827 Blk :=
3828 Make_Block_Statement (Loc,
3829 Declarations => New_List,
3830 Handled_Statement_Sequence =>
3831 Make_Handled_Sequence_Of_Statements (Loc,
3832 Statements => New_List (Relocate_Node (N))));
3834 Add_Block_Identifier (Blk, Blk_Id);
3835 Set_Uses_Sec_Stack (Blk_Id, Manage_Sec_Stack);
3837 Rewrite (N, Blk);
3838 Analyze (N);
3839 end Wrap_Loop_Statement;
3841 -- Local variables
3843 Iter_Spec : constant Node_Id := Iterator_Specification (Iter);
3844 Param_Spec : constant Node_Id := Loop_Parameter_Specification (Iter);
3846 -- Start of processing for Prepare_Loop_Statement
3848 begin
3849 Stop_Processing := False;
3851 if Present (Iter_Spec) then
3852 Prepare_Iterator_Loop (Iter_Spec, Stop_Processing);
3854 elsif Present (Param_Spec) then
3855 Prepare_Param_Spec_Loop (Param_Spec, Stop_Processing);
3856 end if;
3857 end Prepare_Loop_Statement;
3859 -- Local declarations
3861 Id : constant Node_Id := Identifier (N);
3862 Iter : constant Node_Id := Iteration_Scheme (N);
3863 Loc : constant Source_Ptr := Sloc (N);
3864 Ent : Entity_Id;
3865 Stmt : Node_Id;
3867 -- Start of processing for Analyze_Loop_Statement
3869 begin
3870 if Present (Id) then
3872 -- Make name visible, e.g. for use in exit statements. Loop labels
3873 -- are always considered to be referenced.
3875 Analyze (Id);
3876 Ent := Entity (Id);
3878 -- Guard against serious error (typically, a scope mismatch when
3879 -- semantic analysis is requested) by creating loop entity to
3880 -- continue analysis.
3882 if No (Ent) then
3883 if Total_Errors_Detected /= 0 then
3884 Ent := New_Internal_Entity (E_Loop, Current_Scope, Loc, 'L');
3885 else
3886 raise Program_Error;
3887 end if;
3889 -- Verify that the loop name is hot hidden by an unrelated
3890 -- declaration in an inner scope.
3892 elsif Ekind (Ent) /= E_Label and then Ekind (Ent) /= E_Loop then
3893 Error_Msg_Sloc := Sloc (Ent);
3894 Error_Msg_N ("implicit label declaration for & is hidden#", Id);
3896 if Present (Homonym (Ent))
3897 and then Ekind (Homonym (Ent)) = E_Label
3898 then
3899 Set_Entity (Id, Ent);
3900 Mutate_Ekind (Ent, E_Loop);
3901 end if;
3903 else
3904 Generate_Reference (Ent, N, ' ');
3905 Generate_Definition (Ent);
3907 -- If we found a label, mark its type. If not, ignore it, since it
3908 -- means we have a conflicting declaration, which would already
3909 -- have been diagnosed at declaration time. Set Label_Construct
3910 -- of the implicit label declaration, which is not created by the
3911 -- parser for generic units.
3913 if Ekind (Ent) = E_Label then
3914 Reinit_Field_To_Zero (Ent, F_Enclosing_Scope);
3915 Reinit_Field_To_Zero (Ent, F_Reachable);
3916 Mutate_Ekind (Ent, E_Loop);
3918 if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
3919 Set_Label_Construct (Parent (Ent), N);
3920 end if;
3921 end if;
3922 end if;
3924 -- Case of no identifier present. Create one and attach it to the
3925 -- loop statement for use as a scope and as a reference for later
3926 -- expansions. Indicate that the label does not come from source,
3927 -- and attach it to the loop statement so it is part of the tree,
3928 -- even without a full declaration.
3930 else
3931 Ent := New_Internal_Entity (E_Loop, Current_Scope, Loc, 'L');
3932 Set_Etype (Ent, Standard_Void_Type);
3933 Set_Identifier (N, New_Occurrence_Of (Ent, Loc));
3934 Set_Parent (Ent, N);
3935 Set_Has_Created_Identifier (N);
3936 end if;
3938 -- Determine whether the loop statement must be transformed prior to
3939 -- analysis, and if so, perform it. This early modification is needed
3940 -- when:
3942 -- * The loop has an erroneous iteration scheme. In this case the
3943 -- loop is converted into an infinite loop in order to perform
3944 -- minor analysis.
3946 -- * The loop is an Ada 2012 iterator loop. In this case the loop is
3947 -- wrapped within a block to provide a local scope for the iterator.
3948 -- If the iterator specification requires the secondary stack in any
3949 -- way, the block is marked in order to manage it.
3951 -- * The loop is using a parameter specification where the discrete
3952 -- range requires the secondary stack. In this case the loop is
3953 -- wrapped within a block in order to manage the secondary stack.
3955 -- ??? This overlooks finalization: the loop may leave the secondary
3956 -- stack untouched, but its iterator or discrete range may need
3957 -- finalization, in which case the block is also required. Therefore
3958 -- the criterion must be based on Sem_Util.Requires_Transient_Scope,
3959 -- which happens to be what is currently implemented.
3961 if Present (Iter) then
3962 declare
3963 Stop_Processing : Boolean;
3964 begin
3965 Prepare_Loop_Statement (Iter, Stop_Processing);
3967 if Stop_Processing then
3968 return;
3969 end if;
3970 end;
3971 end if;
3973 -- Kill current values on entry to loop, since statements in the body of
3974 -- the loop may have been executed before the loop is entered. Similarly
3975 -- we kill values after the loop, since we do not know that the body of
3976 -- the loop was executed.
3978 Kill_Current_Values;
3979 Push_Scope (Ent);
3980 Analyze_Iteration_Scheme (Iter);
3982 -- Check for following case which merits a warning if the type E of is
3983 -- a multi-dimensional array (and no explicit subscript ranges present).
3985 -- for J in E'Range
3986 -- for K in E'Range
3988 if Present (Iter)
3989 and then Present (Loop_Parameter_Specification (Iter))
3990 then
3991 declare
3992 LPS : constant Node_Id := Loop_Parameter_Specification (Iter);
3993 DSD : constant Node_Id :=
3994 Original_Node (Discrete_Subtype_Definition (LPS));
3995 begin
3996 if Nkind (DSD) = N_Attribute_Reference
3997 and then Attribute_Name (DSD) = Name_Range
3998 and then No (Expressions (DSD))
3999 then
4000 declare
4001 Typ : constant Entity_Id := Etype (Prefix (DSD));
4002 begin
4003 if Is_Array_Type (Typ)
4004 and then Number_Dimensions (Typ) > 1
4005 and then Nkind (Parent (N)) = N_Loop_Statement
4006 and then Present (Iteration_Scheme (Parent (N)))
4007 then
4008 declare
4009 OIter : constant Node_Id :=
4010 Iteration_Scheme (Parent (N));
4011 OLPS : constant Node_Id :=
4012 Loop_Parameter_Specification (OIter);
4013 ODSD : constant Node_Id :=
4014 Original_Node (Discrete_Subtype_Definition (OLPS));
4015 begin
4016 if Nkind (ODSD) = N_Attribute_Reference
4017 and then Attribute_Name (ODSD) = Name_Range
4018 and then No (Expressions (ODSD))
4019 and then Etype (Prefix (ODSD)) = Typ
4020 then
4021 Error_Msg_Sloc := Sloc (ODSD);
4022 Error_Msg_N
4023 ("inner range same as outer range#??", DSD);
4024 end if;
4025 end;
4026 end if;
4027 end;
4028 end if;
4029 end;
4030 end if;
4032 -- Analyze the statements of the body except in the case of an Ada 2012
4033 -- iterator with the expander active. In this case the expander will do
4034 -- a rewrite of the loop into a while loop. We will then analyze the
4035 -- loop body when we analyze this while loop.
4037 -- We need to do this delay because if the container is for indefinite
4038 -- types the actual subtype of the components will only be determined
4039 -- when the cursor declaration is analyzed.
4041 -- If the expander is not active then we want to analyze the loop body
4042 -- now even in the Ada 2012 iterator case, since the rewriting will not
4043 -- be done. Insert the loop variable in the current scope, if not done
4044 -- when analysing the iteration scheme. Set its kind properly to detect
4045 -- improper uses in the loop body.
4047 -- In GNATprove mode, we do one of the above depending on the kind of
4048 -- loop. If it is an iterator over an array, then we do not analyze the
4049 -- loop now. We will analyze it after it has been rewritten by the
4050 -- special SPARK expansion which is activated in GNATprove mode. We need
4051 -- to do this so that other expansions that should occur in GNATprove
4052 -- mode take into account the specificities of the rewritten loop, in
4053 -- particular the introduction of a renaming (which needs to be
4054 -- expanded).
4056 -- In other cases in GNATprove mode then we want to analyze the loop
4057 -- body now, since no rewriting will occur. Within a generic the
4058 -- GNATprove mode is irrelevant, we must analyze the generic for
4059 -- non-local name capture.
4061 if Present (Iter)
4062 and then Present (Iterator_Specification (Iter))
4063 then
4064 if GNATprove_Mode
4065 and then Is_Iterator_Over_Array (Iterator_Specification (Iter))
4066 and then not Inside_A_Generic
4067 then
4068 null;
4070 elsif not Expander_Active then
4071 declare
4072 I_Spec : constant Node_Id := Iterator_Specification (Iter);
4073 Id : constant Entity_Id := Defining_Identifier (I_Spec);
4075 begin
4076 if Scope (Id) /= Current_Scope then
4077 Enter_Name (Id);
4078 end if;
4080 -- In an element iterator, the loop parameter is a variable if
4081 -- the domain of iteration (container or array) is a variable.
4083 if not Of_Present (I_Spec)
4084 or else not Is_Variable (Name (I_Spec))
4085 then
4086 Mutate_Ekind (Id, E_Loop_Parameter);
4087 end if;
4088 end;
4090 Analyze_Statements (Statements (N));
4091 end if;
4093 else
4094 -- Pre-Ada2012 for-loops and while loops
4096 Analyze_Statements (Statements (N));
4097 end if;
4099 -- If the loop has no side effects, mark it for removal.
4101 if Side_Effect_Free_Loop (N) then
4102 Set_Is_Null_Loop (N);
4103 end if;
4105 -- When the iteration scheme of a loop contains attribute 'Loop_Entry,
4106 -- the loop is transformed into a conditional block. Retrieve the loop.
4108 Stmt := N;
4110 if Subject_To_Loop_Entry_Attributes (Stmt) then
4111 Stmt := Find_Loop_In_Conditional_Block (Stmt);
4112 end if;
4114 -- Finish up processing for the loop. We kill all current values, since
4115 -- in general we don't know if the statements in the loop have been
4116 -- executed. We could do a bit better than this with a loop that we
4117 -- know will execute at least once, but it's not worth the trouble and
4118 -- the front end is not in the business of flow tracing.
4120 Process_End_Label (Stmt, 'e', Ent);
4121 End_Scope;
4122 Kill_Current_Values;
4124 -- Check for infinite loop. Skip check for generated code, since it
4125 -- justs waste time and makes debugging the routine called harder.
4127 -- Note that we have to wait till the body of the loop is fully analyzed
4128 -- before making this call, since Check_Infinite_Loop_Warning relies on
4129 -- being able to use semantic visibility information to find references.
4131 if Comes_From_Source (Stmt) then
4132 Check_Infinite_Loop_Warning (Stmt);
4133 end if;
4135 -- Code after loop is unreachable if the loop has no WHILE or FOR and
4136 -- contains no EXIT statements within the body of the loop.
4138 if No (Iter) and then not Has_Exit (Ent) then
4139 Check_Unreachable_Code (Stmt);
4140 end if;
4141 end Analyze_Loop_Statement;
4143 ----------------------------
4144 -- Analyze_Null_Statement --
4145 ----------------------------
4147 -- Note: the semantics of the null statement is implemented by a single
4148 -- null statement, too bad everything isn't as simple as this.
4150 procedure Analyze_Null_Statement (N : Node_Id) is
4151 pragma Warnings (Off, N);
4152 begin
4153 null;
4154 end Analyze_Null_Statement;
4156 -------------------------
4157 -- Analyze_Target_Name --
4158 -------------------------
4160 procedure Analyze_Target_Name (N : Node_Id) is
4161 procedure Report_Error;
4162 -- Complain about illegal use of target_name and rewrite it into unknown
4163 -- identifier.
4165 ------------------
4166 -- Report_Error --
4167 ------------------
4169 procedure Report_Error is
4170 begin
4171 Error_Msg_N
4172 ("must appear in the right-hand side of an assignment statement",
4174 Rewrite (N, New_Occurrence_Of (Any_Id, Sloc (N)));
4175 end Report_Error;
4177 -- Start of processing for Analyze_Target_Name
4179 begin
4180 -- A target name has the type of the left-hand side of the enclosing
4181 -- assignment.
4183 -- First, verify that the context is the right-hand side of an
4184 -- assignment statement.
4186 if No (Current_Assignment) then
4187 Report_Error;
4188 return;
4189 end if;
4191 declare
4192 Current : Node_Id := N;
4193 Context : Node_Id := Parent (N);
4194 begin
4195 while Present (Context) loop
4197 -- Check if target_name appears in the expression of the enclosing
4198 -- assignment.
4200 if Nkind (Context) = N_Assignment_Statement then
4201 if Current = Expression (Context) then
4202 pragma Assert (Context = Current_Assignment);
4203 Set_Etype (N, Etype (Name (Current_Assignment)));
4204 else
4205 Report_Error;
4206 end if;
4207 return;
4209 -- Prevent the search from going too far
4211 elsif Is_Body_Or_Package_Declaration (Context) then
4212 Report_Error;
4213 return;
4214 end if;
4216 Current := Context;
4217 Context := Parent (Context);
4218 end loop;
4220 Report_Error;
4221 end;
4222 end Analyze_Target_Name;
4224 ------------------------
4225 -- Analyze_Statements --
4226 ------------------------
4228 procedure Analyze_Statements (L : List_Id) is
4229 Lab : Entity_Id;
4230 S : Node_Id;
4232 begin
4233 -- The labels declared in the statement list are reachable from
4234 -- statements in the list. We do this as a prepass so that any goto
4235 -- statement will be properly flagged if its target is not reachable.
4236 -- This is not required, but is nice behavior.
4238 S := First (L);
4239 while Present (S) loop
4240 if Nkind (S) = N_Label then
4241 Analyze (Identifier (S));
4242 Lab := Entity (Identifier (S));
4244 -- If we found a label mark it as reachable
4246 if Ekind (Lab) = E_Label then
4247 Generate_Definition (Lab);
4248 Set_Reachable (Lab);
4250 if Nkind (Parent (Lab)) = N_Implicit_Label_Declaration then
4251 Set_Label_Construct (Parent (Lab), S);
4252 end if;
4254 -- If we failed to find a label, it means the implicit declaration
4255 -- of the label was hidden. A for-loop parameter can do this to
4256 -- a label with the same name inside the loop, since the implicit
4257 -- label declaration is in the innermost enclosing body or block
4258 -- statement.
4260 else
4261 Error_Msg_Sloc := Sloc (Lab);
4262 Error_Msg_N
4263 ("implicit label declaration for & is hidden#",
4264 Identifier (S));
4265 end if;
4266 end if;
4268 Next (S);
4269 end loop;
4271 -- Perform semantic analysis on all statements
4273 Conditional_Statements_Begin;
4275 S := First (L);
4276 while Present (S) loop
4277 Analyze (S);
4279 -- Remove dimension in all statements
4281 Remove_Dimension_In_Statement (S);
4282 Next (S);
4283 end loop;
4285 Conditional_Statements_End;
4287 -- Make labels unreachable. Visibility is not sufficient, because labels
4288 -- in one if-branch for example are not reachable from the other branch,
4289 -- even though their declarations are in the enclosing declarative part.
4291 S := First (L);
4292 while Present (S) loop
4293 if Nkind (S) = N_Label
4294 and then Ekind (Entity (Identifier (S))) = E_Label
4295 then
4296 Set_Reachable (Entity (Identifier (S)), False);
4297 end if;
4299 Next (S);
4300 end loop;
4301 end Analyze_Statements;
4303 ----------------------------
4304 -- Check_Unreachable_Code --
4305 ----------------------------
4307 procedure Check_Unreachable_Code (N : Node_Id) is
4309 function Is_Simple_Case (N : Node_Id) return Boolean;
4310 -- N is the condition of an if statement. True if N is simple enough
4311 -- that we should not set Unblocked_Exit_Count in the special case
4312 -- below.
4314 --------------------
4315 -- Is_Simple_Case --
4316 --------------------
4318 function Is_Simple_Case (N : Node_Id) return Boolean is
4319 begin
4320 return
4321 Is_Trivial_Boolean (N)
4322 or else
4323 (Comes_From_Source (N)
4324 and then Is_Static_Expression (N)
4325 and then Nkind (N) in N_Identifier | N_Expanded_Name
4326 and then Ekind (Entity (N)) = E_Constant)
4327 or else
4328 (not In_Instance
4329 and then Nkind (Original_Node (N)) = N_Op_Not
4330 and then Is_Simple_Case (Right_Opnd (Original_Node (N))));
4331 end Is_Simple_Case;
4333 Error_Node : Node_Id;
4334 Nxt : Node_Id;
4335 P : Node_Id;
4337 begin
4338 if Comes_From_Source (N) then
4339 Nxt := Original_Node (Next (N));
4341 -- Skip past pragmas
4343 while Nkind (Nxt) = N_Pragma loop
4344 Nxt := Original_Node (Next (Nxt));
4345 end loop;
4347 -- If a label follows us, then we never have dead code, since someone
4348 -- could branch to the label, so we just ignore it.
4350 if Nkind (Nxt) = N_Label then
4351 return;
4353 -- Otherwise see if we have a real statement following us
4355 elsif Comes_From_Source (Nxt)
4356 and then Is_Statement (Nxt)
4357 then
4358 -- Special very annoying exception. Ada RM 6.5(5) annoyingly
4359 -- requires functions to have at least one return statement, so
4360 -- don't complain about a simple return that follows a raise or a
4361 -- call to procedure with No_Return.
4363 if not (Present (Current_Subprogram)
4364 and then Ekind (Current_Subprogram) = E_Function
4365 and then (Nkind (N) in N_Raise_Statement
4366 or else
4367 (Nkind (N) = N_Procedure_Call_Statement
4368 and then Is_Entity_Name (Name (N))
4369 and then Present (Entity (Name (N)))
4370 and then No_Return (Entity (Name (N)))))
4371 and then Nkind (Nxt) = N_Simple_Return_Statement)
4372 then
4373 -- The rather strange shenanigans with the warning message
4374 -- here reflects the fact that Kill_Dead_Code is very good at
4375 -- removing warnings in deleted code, and this is one warning
4376 -- we would prefer NOT to have removed.
4378 Error_Node := Nxt;
4380 -- If we have unreachable code, analyze and remove the
4381 -- unreachable code, since it is useless and we don't want
4382 -- to generate junk warnings.
4384 -- We skip this step if we are not in code generation mode.
4386 -- This is the one case where we remove dead code in the
4387 -- semantics as opposed to the expander, and we do not want
4388 -- to remove code if we are not in code generation mode, since
4389 -- this messes up the tree or loses useful information for
4390 -- analysis tools such as CodePeer.
4392 -- Note that one might react by moving the whole circuit to
4393 -- exp_ch5, but then we lose the warning in -gnatc mode.
4395 if Operating_Mode = Generate_Code then
4396 loop
4397 declare
4398 Del : constant Node_Id := Next (N);
4399 -- Node to be possibly deleted
4400 begin
4401 -- Quit deleting when we have nothing more to delete
4402 -- or if we hit a label (since someone could transfer
4403 -- control to a label, so we should not delete it).
4405 exit when No (Del) or else Nkind (Del) = N_Label;
4407 -- Statement/declaration is to be deleted
4409 Analyze (Del);
4410 Kill_Dead_Code (Del);
4411 Remove (Del);
4412 end;
4413 end loop;
4415 -- If this is a function, we add "raise Program_Error;",
4416 -- because otherwise, we will get incorrect warnings about
4417 -- falling off the end of the function.
4419 declare
4420 Subp : constant Entity_Id := Current_Subprogram;
4421 begin
4422 if Present (Subp) and then Ekind (Subp) = E_Function then
4423 Insert_After_And_Analyze (N,
4424 Make_Raise_Program_Error (Sloc (Error_Node),
4425 Reason => PE_Missing_Return));
4426 end if;
4427 end;
4429 end if;
4431 -- Suppress the warning in instances, because a statement can
4432 -- be unreachable in some instances but not others.
4434 if not In_Instance then
4435 Error_Msg_N ("??unreachable code!", Error_Node);
4436 end if;
4437 end if;
4439 -- If the unconditional transfer of control instruction is the
4440 -- last statement of a sequence, then see if our parent is one of
4441 -- the constructs for which we count unblocked exits, and if so,
4442 -- adjust the count.
4444 else
4445 P := Parent (N);
4447 -- Statements in THEN part or ELSE part of IF statement
4449 if Nkind (P) = N_If_Statement then
4450 null;
4452 -- Statements in ELSIF part of an IF statement
4454 elsif Nkind (P) = N_Elsif_Part then
4455 P := Parent (P);
4456 pragma Assert (Nkind (P) = N_If_Statement);
4458 -- Statements in CASE statement alternative
4460 elsif Nkind (P) = N_Case_Statement_Alternative then
4461 P := Parent (P);
4462 pragma Assert (Nkind (P) = N_Case_Statement);
4464 -- Statements in body of block
4466 elsif Nkind (P) = N_Handled_Sequence_Of_Statements
4467 and then Nkind (Parent (P)) = N_Block_Statement
4468 then
4469 -- The original loop is now placed inside a block statement
4470 -- due to the expansion of attribute 'Loop_Entry. Return as
4471 -- this is not a "real" block for the purposes of exit
4472 -- counting.
4474 if Nkind (N) = N_Loop_Statement
4475 and then Subject_To_Loop_Entry_Attributes (N)
4476 then
4477 return;
4478 end if;
4480 -- Statements in exception handler in a block
4482 elsif Nkind (P) = N_Exception_Handler
4483 and then Nkind (Parent (P)) = N_Handled_Sequence_Of_Statements
4484 and then Nkind (Parent (Parent (P))) = N_Block_Statement
4485 then
4486 null;
4488 -- None of these cases, so return
4490 else
4491 return;
4492 end if;
4494 -- This was one of the cases we are looking for (i.e. the parent
4495 -- construct was IF, CASE or block). In most cases, we simply
4496 -- decrement the count. However, if the parent is something like:
4498 -- if cond then
4499 -- raise ...; -- or some other jump
4500 -- end if;
4502 -- where cond is an expression that is known-true at compile time,
4503 -- we can treat that as just the jump -- i.e. anything following
4504 -- the if statement is unreachable. We don't do this for simple
4505 -- cases like "if True" or "if Debug_Flag", because that causes
4506 -- too many warnings.
4508 if Nkind (P) = N_If_Statement
4509 and then Present (Then_Statements (P))
4510 and then No (Elsif_Parts (P))
4511 and then No (Else_Statements (P))
4512 and then Is_OK_Static_Expression (Condition (P))
4513 and then Is_True (Expr_Value (Condition (P)))
4514 and then not Is_Simple_Case (Condition (P))
4515 then
4516 pragma Assert (Unblocked_Exit_Count = 2);
4517 Unblocked_Exit_Count := 0;
4518 else
4519 Unblocked_Exit_Count := Unblocked_Exit_Count - 1;
4520 end if;
4521 end if;
4522 end if;
4523 end Check_Unreachable_Code;
4525 ------------------------
4526 -- Has_Sec_Stack_Call --
4527 ------------------------
4529 function Has_Sec_Stack_Call (N : Node_Id) return Boolean is
4530 function Check_Call (N : Node_Id) return Traverse_Result;
4531 -- Check if N is a function call which uses the secondary stack
4533 ----------------
4534 -- Check_Call --
4535 ----------------
4537 function Check_Call (N : Node_Id) return Traverse_Result is
4538 Nam : Node_Id;
4539 Subp : Entity_Id;
4540 Typ : Entity_Id;
4542 begin
4543 if Nkind (N) = N_Function_Call then
4544 Nam := Name (N);
4546 -- Obtain the subprogram being invoked
4548 loop
4549 if Nkind (Nam) = N_Explicit_Dereference then
4550 Nam := Prefix (Nam);
4552 elsif Nkind (Nam) = N_Selected_Component then
4553 Nam := Selector_Name (Nam);
4555 else
4556 exit;
4557 end if;
4558 end loop;
4560 Subp := Entity (Nam);
4562 if Present (Subp) then
4563 Typ := Etype (Subp);
4565 if Requires_Transient_Scope (Typ) then
4566 return Abandon;
4568 elsif Sec_Stack_Needed_For_Return (Subp) then
4569 return Abandon;
4570 end if;
4571 end if;
4572 end if;
4574 -- Continue traversing the tree
4576 return OK;
4577 end Check_Call;
4579 function Check_Calls is new Traverse_Func (Check_Call);
4581 -- Start of processing for Has_Sec_Stack_Call
4583 begin
4584 return Check_Calls (N) = Abandon;
4585 end Has_Sec_Stack_Call;
4587 ----------------------
4588 -- Preanalyze_Range --
4589 ----------------------
4591 procedure Preanalyze_Range (R_Copy : Node_Id) is
4592 Save_Analysis : constant Boolean := Full_Analysis;
4593 Typ : Entity_Id;
4595 begin
4596 Full_Analysis := False;
4597 Expander_Mode_Save_And_Set (False);
4599 -- In addition to the above we must explicitly suppress the generation
4600 -- of freeze nodes that might otherwise be generated during resolution
4601 -- of the range (e.g. if given by an attribute that will freeze its
4602 -- prefix).
4604 Set_Must_Not_Freeze (R_Copy);
4606 if Nkind (R_Copy) = N_Attribute_Reference then
4607 Set_Must_Not_Freeze (Prefix (R_Copy));
4608 end if;
4610 Analyze (R_Copy);
4612 if Nkind (R_Copy) in N_Subexpr and then Is_Overloaded (R_Copy) then
4614 -- Apply preference rules for range of predefined integer types, or
4615 -- check for array or iterable construct for "of" iterator, or
4616 -- diagnose true ambiguity.
4618 declare
4619 I : Interp_Index;
4620 It : Interp;
4621 Found : Entity_Id := Empty;
4623 begin
4624 Get_First_Interp (R_Copy, I, It);
4625 while Present (It.Typ) loop
4626 if Is_Discrete_Type (It.Typ) then
4627 if No (Found) then
4628 Found := It.Typ;
4629 else
4630 if Scope (Found) = Standard_Standard then
4631 null;
4633 elsif Scope (It.Typ) = Standard_Standard then
4634 Found := It.Typ;
4636 else
4637 -- Both of them are user-defined
4639 Error_Msg_N
4640 ("ambiguous bounds in range of iteration", R_Copy);
4641 Error_Msg_N ("\possible interpretations:", R_Copy);
4642 Error_Msg_NE ("\\}", R_Copy, Found);
4643 Error_Msg_NE ("\\}", R_Copy, It.Typ);
4644 exit;
4645 end if;
4646 end if;
4648 elsif Nkind (Parent (R_Copy)) = N_Iterator_Specification
4649 and then Of_Present (Parent (R_Copy))
4650 then
4651 if Is_Array_Type (It.Typ)
4652 or else Has_Aspect (It.Typ, Aspect_Iterator_Element)
4653 or else Has_Aspect (It.Typ, Aspect_Constant_Indexing)
4654 or else Has_Aspect (It.Typ, Aspect_Variable_Indexing)
4655 then
4656 if No (Found) then
4657 Found := It.Typ;
4658 Set_Etype (R_Copy, It.Typ);
4660 else
4661 Error_Msg_N ("ambiguous domain of iteration", R_Copy);
4662 end if;
4663 end if;
4664 end if;
4666 Get_Next_Interp (I, It);
4667 end loop;
4668 end;
4669 end if;
4671 -- Subtype mark in iteration scheme
4673 if Is_Entity_Name (R_Copy) and then Is_Type (Entity (R_Copy)) then
4674 null;
4676 -- Expression in range, or Ada 2012 iterator
4678 elsif Nkind (R_Copy) in N_Subexpr then
4679 Resolve (R_Copy);
4680 Typ := Etype (R_Copy);
4682 if Is_Discrete_Type (Typ) then
4683 null;
4685 -- Check that the resulting object is an iterable container
4687 elsif Has_Aspect (Typ, Aspect_Iterator_Element)
4688 or else Has_Aspect (Typ, Aspect_Constant_Indexing)
4689 or else Has_Aspect (Typ, Aspect_Variable_Indexing)
4690 then
4691 null;
4693 -- The expression may yield an implicit reference to an iterable
4694 -- container. Insert explicit dereference so that proper type is
4695 -- visible in the loop.
4697 elsif Has_Implicit_Dereference (Etype (R_Copy)) then
4698 Build_Explicit_Dereference
4699 (R_Copy, Get_Reference_Discriminant (Etype (R_Copy)));
4700 end if;
4701 end if;
4703 Expander_Mode_Restore;
4704 Full_Analysis := Save_Analysis;
4705 end Preanalyze_Range;
4707 end Sem_Ch5;