Add assember CFI directives to millicode division and remainder routines.
[official-gcc.git] / gcc / ada / sem_ch5.adb
blobab5a2083a00dbafd69533ee02947e06030de0a6a
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-2023, 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 Namet; use Namet;
43 with Nlists; use Nlists;
44 with Nmake; use Nmake;
45 with Opt; use Opt;
46 with Sem; use Sem;
47 with Sem_Aux; use Sem_Aux;
48 with Sem_Case; use Sem_Case;
49 with Sem_Ch3; use Sem_Ch3;
50 with Sem_Ch6; use Sem_Ch6;
51 with Sem_Ch8; use Sem_Ch8;
52 with Sem_Dim; use Sem_Dim;
53 with Sem_Disp; use Sem_Disp;
54 with Sem_Elab; use Sem_Elab;
55 with Sem_Eval; use Sem_Eval;
56 with Sem_Res; use Sem_Res;
57 with Sem_Type; use Sem_Type;
58 with Sem_Util; use Sem_Util;
59 with Sem_Warn; use Sem_Warn;
60 with Snames; use Snames;
61 with Stand; use Stand;
62 with Sinfo; use Sinfo;
63 with Sinfo.Nodes; use Sinfo.Nodes;
64 with Sinfo.Utils; use Sinfo.Utils;
65 with Targparm; use Targparm;
66 with Tbuild; use Tbuild;
67 with Ttypes; use Ttypes;
68 with Uintp; use Uintp;
69 with Warnsw; use Warnsw;
71 package body Sem_Ch5 is
73 Current_Assignment : Node_Id := Empty;
74 -- This variable holds the node for an assignment that contains target
75 -- names. The corresponding flag has been set by the parser, and when
76 -- set the analysis of the RHS must be done with all expansion disabled,
77 -- because the assignment is reanalyzed after expansion has replaced all
78 -- occurrences of the target name appropriately.
80 Unblocked_Exit_Count : Nat := 0;
81 -- This variable is used when processing if statements, case statements,
82 -- and block statements. It counts the number of exit points that are not
83 -- blocked by unconditional transfer instructions: for IF and CASE, these
84 -- are the branches of the conditional; for a block, they are the statement
85 -- sequence of the block, and the statement sequences of any exception
86 -- handlers that are part of the block. When processing is complete, if
87 -- this count is zero, it means that control cannot fall through the IF,
88 -- CASE or block statement. This is used for the generation of warning
89 -- messages. This variable is recursively saved on entry to processing the
90 -- construct, and restored on exit.
92 function Has_Sec_Stack_Call (N : Node_Id) return Boolean;
93 -- N is the node for an arbitrary construct. This function searches the
94 -- construct N to see if any expressions within it contain function
95 -- calls that use the secondary stack, returning True if any such call
96 -- is found, and False otherwise.
98 procedure Preanalyze_Range (R_Copy : Node_Id);
99 -- Determine expected type of range or domain of iteration of Ada 2012
100 -- loop by analyzing separate copy. Do the analysis and resolution of the
101 -- copy of the bound(s) with expansion disabled, to prevent the generation
102 -- of finalization actions. This prevents memory leaks when the bounds
103 -- contain calls to functions returning controlled arrays or when the
104 -- domain of iteration is a container.
106 ------------------------
107 -- Analyze_Assignment --
108 ------------------------
110 -- WARNING: This routine manages Ghost regions. Return statements must be
111 -- replaced by gotos which jump to the end of the routine and restore the
112 -- Ghost mode.
114 procedure Analyze_Assignment (N : Node_Id) is
115 Lhs : constant Node_Id := Name (N);
116 Rhs : Node_Id := Expression (N);
118 procedure Diagnose_Non_Variable_Lhs (N : Node_Id);
119 -- N is the node for the left hand side of an assignment, and it is not
120 -- a variable. This routine issues an appropriate diagnostic.
122 function Is_Protected_Part_Of_Constituent
123 (Nod : Node_Id) return Boolean;
124 -- Determine whether arbitrary node Nod denotes a Part_Of constituent of
125 -- a single protected type.
127 procedure Kill_Lhs;
128 -- This is called to kill current value settings of a simple variable
129 -- on the left hand side. We call it if we find any error in analyzing
130 -- the assignment, and at the end of processing before setting any new
131 -- current values in place.
133 procedure Set_Assignment_Type
134 (Opnd : Node_Id;
135 Opnd_Type : in out Entity_Id);
136 -- Opnd is either the Lhs or Rhs of the assignment, and Opnd_Type is the
137 -- nominal subtype. This procedure is used to deal with cases where the
138 -- nominal subtype must be replaced by the actual subtype.
140 procedure Transform_BIP_Assignment (Typ : Entity_Id);
141 function Should_Transform_BIP_Assignment
142 (Typ : Entity_Id) return Boolean;
143 -- If the right-hand side of an assignment statement is a build-in-place
144 -- call we cannot build in place, so we insert a temp initialized with
145 -- the call, and transform the assignment statement to copy the temp.
146 -- Transform_BIP_Assignment does the transformation, and
147 -- Should_Transform_BIP_Assignment determines whether we should.
148 -- The same goes for qualified expressions and conversions whose
149 -- operand is such a call.
151 -- This is only for nonlimited types; assignment statements are illegal
152 -- for limited types, but are generated internally for aggregates and
153 -- init procs. These limited-type are not really assignment statements
154 -- -- conceptually, they are initializations, so should not be
155 -- transformed.
157 -- Similarly, for nonlimited types, aggregates and init procs generate
158 -- assignment statements that are really initializations. These are
159 -- marked No_Ctrl_Actions.
161 function Within_Function return Boolean;
162 -- Determine whether the current scope is a function or appears within
163 -- one.
165 -------------------------------
166 -- Diagnose_Non_Variable_Lhs --
167 -------------------------------
169 procedure Diagnose_Non_Variable_Lhs (N : Node_Id) is
170 begin
171 -- Not worth posting another error if left hand side already flagged
172 -- as being illegal in some respect.
174 if Error_Posted (N) then
175 return;
177 -- Some special bad cases of entity names
179 elsif Is_Entity_Name (N) then
180 declare
181 Ent : constant Entity_Id := Entity (N);
183 begin
184 if Ekind (Ent) = E_Loop_Parameter
185 or else Is_Loop_Parameter (Ent)
186 then
187 Error_Msg_N ("assignment to loop parameter not allowed", N);
188 return;
190 elsif Ekind (Ent) = E_In_Parameter then
191 Error_Msg_N
192 ("assignment to IN mode parameter not allowed", N);
193 return;
195 -- Renamings of protected private components are turned into
196 -- constants when compiling a protected function. In the case
197 -- of single protected types, the private component appears
198 -- directly.
200 elsif (Is_Prival (Ent) and then Within_Function)
201 or else Is_Protected_Component (Ent)
202 then
203 Error_Msg_N
204 ("protected function cannot modify its protected object",
206 return;
207 end if;
208 end;
210 -- For indexed components, test prefix if it is in array. We do not
211 -- want to recurse for cases where the prefix is a pointer, since we
212 -- may get a message confusing the pointer and what it references.
214 elsif Nkind (N) = N_Indexed_Component
215 and then Is_Array_Type (Etype (Prefix (N)))
216 then
217 Diagnose_Non_Variable_Lhs (Prefix (N));
218 return;
220 -- Another special case for assignment to discriminant
222 elsif Nkind (N) = N_Selected_Component then
223 if Present (Entity (Selector_Name (N)))
224 and then Ekind (Entity (Selector_Name (N))) = E_Discriminant
225 then
226 Error_Msg_N ("assignment to discriminant not allowed", N);
227 return;
229 -- For selection from record, diagnose prefix, but note that again
230 -- we only do this for a record, not e.g. for a pointer.
232 elsif Is_Record_Type (Etype (Prefix (N))) then
233 Diagnose_Non_Variable_Lhs (Prefix (N));
234 return;
235 end if;
236 end if;
238 -- If we fall through, we have no special message to issue
240 Error_Msg_N ("left hand side of assignment must be a variable", N);
241 end Diagnose_Non_Variable_Lhs;
243 --------------------------------------
244 -- Is_Protected_Part_Of_Constituent --
245 --------------------------------------
247 function Is_Protected_Part_Of_Constituent
248 (Nod : Node_Id) return Boolean
250 Encap_Id : Entity_Id;
251 Var_Id : Entity_Id;
253 begin
254 -- Abstract states and variables may act as Part_Of constituents of
255 -- single protected types, however only variables can be modified by
256 -- an assignment.
258 if Is_Entity_Name (Nod) then
259 Var_Id := Entity (Nod);
261 if Present (Var_Id) and then Ekind (Var_Id) = E_Variable then
262 Encap_Id := Encapsulating_State (Var_Id);
264 -- To qualify, the node must denote a reference to a variable
265 -- whose encapsulating state is a single protected object.
267 return
268 Present (Encap_Id)
269 and then Is_Single_Protected_Object (Encap_Id);
270 end if;
271 end if;
273 return False;
274 end Is_Protected_Part_Of_Constituent;
276 --------------
277 -- Kill_Lhs --
278 --------------
280 procedure Kill_Lhs is
281 begin
282 if Is_Entity_Name (Lhs) then
283 declare
284 Ent : constant Entity_Id := Entity (Lhs);
285 begin
286 if Present (Ent) then
287 Kill_Current_Values (Ent);
288 end if;
289 end;
290 end if;
291 end Kill_Lhs;
293 -------------------------
294 -- Set_Assignment_Type --
295 -------------------------
297 procedure Set_Assignment_Type
298 (Opnd : Node_Id;
299 Opnd_Type : in out Entity_Id)
301 Decl : Node_Id;
303 begin
304 Require_Entity (Opnd);
306 -- If the assignment operand is an in-out or out parameter, then we
307 -- get the actual subtype (needed for the unconstrained case). If the
308 -- operand is the actual in an entry declaration, then within the
309 -- accept statement it is replaced with a local renaming, which may
310 -- also have an actual subtype. Likewise for a return object that
311 -- lives on the secondary stack.
313 if Is_Entity_Name (Opnd)
314 and then (Ekind (Entity (Opnd)) in E_Out_Parameter
315 | E_In_Out_Parameter
316 | E_Generic_In_Out_Parameter
317 or else
318 (Ekind (Entity (Opnd)) = E_Variable
319 and then Nkind (Parent (Entity (Opnd))) =
320 N_Object_Renaming_Declaration
321 and then Nkind (Parent (Parent (Entity (Opnd)))) =
322 N_Accept_Statement)
323 or else Is_Secondary_Stack_Return_Object (Entity (Opnd)))
324 then
325 Opnd_Type := Get_Actual_Subtype (Opnd);
327 -- If assignment operand is a component reference, then we get the
328 -- actual subtype of the component for the unconstrained case.
330 elsif Nkind (Opnd) in N_Selected_Component | N_Explicit_Dereference
331 and then not Is_Unchecked_Union (Opnd_Type)
332 then
333 Decl := Build_Actual_Subtype_Of_Component (Opnd_Type, Opnd);
335 if Present (Decl) then
336 Insert_Action (N, Decl);
337 Mark_Rewrite_Insertion (Decl);
338 Analyze (Decl);
339 Opnd_Type := Defining_Identifier (Decl);
340 Set_Etype (Opnd, Opnd_Type);
341 Freeze_Itype (Opnd_Type, N);
343 elsif Is_Constrained (Etype (Opnd)) then
344 Opnd_Type := Etype (Opnd);
345 end if;
347 -- For slice, use the constrained subtype created for the slice
349 elsif Nkind (Opnd) = N_Slice then
350 Opnd_Type := Etype (Opnd);
351 end if;
352 end Set_Assignment_Type;
354 -------------------------------------
355 -- Should_Transform_BIP_Assignment --
356 -------------------------------------
358 function Should_Transform_BIP_Assignment
359 (Typ : Entity_Id) return Boolean
361 begin
362 if Expander_Active
363 and then not Is_Limited_View (Typ)
364 and then Is_Build_In_Place_Result_Type (Typ)
365 and then not No_Ctrl_Actions (N)
366 then
367 -- This function is called early, before name resolution is
368 -- complete, so we have to deal with things that might turn into
369 -- function calls later. N_Function_Call and N_Op nodes are the
370 -- obvious case. An N_Identifier or N_Expanded_Name is a
371 -- parameterless function call if it denotes a function.
372 -- Finally, an attribute reference can be a function call.
374 declare
375 Unqual_Rhs : constant Node_Id := Unqual_Conv (Rhs);
376 begin
377 case Nkind (Unqual_Rhs) is
378 when N_Function_Call
379 | N_Op
381 return True;
383 when N_Expanded_Name
384 | N_Identifier
386 return
387 Ekind (Entity (Unqual_Rhs)) in E_Function | E_Operator;
389 -- T'Input will turn into a call whose result type is T
391 when N_Attribute_Reference =>
392 return Attribute_Name (Unqual_Rhs) = Name_Input;
394 when others =>
395 return False;
396 end case;
397 end;
398 else
399 return False;
400 end if;
401 end Should_Transform_BIP_Assignment;
403 ------------------------------
404 -- Transform_BIP_Assignment --
405 ------------------------------
407 procedure Transform_BIP_Assignment (Typ : Entity_Id) is
409 -- Tranform "X : [constant] T := F (...);" into:
411 -- Temp : constant T := F (...);
412 -- X := Temp;
414 Loc : constant Source_Ptr := Sloc (N);
415 Def_Id : constant Entity_Id := Make_Temporary (Loc, 'Y', Rhs);
416 Obj_Decl : constant Node_Id :=
417 Make_Object_Declaration (Loc,
418 Defining_Identifier => Def_Id,
419 Constant_Present => True,
420 Object_Definition => New_Occurrence_Of (Typ, Loc),
421 Expression => Rhs,
422 Has_Init_Expression => True);
424 begin
425 Set_Etype (Def_Id, Typ);
426 Set_Expression (N, New_Occurrence_Of (Def_Id, Loc));
428 -- At this point, Rhs is no longer equal to Expression (N), so:
430 Rhs := Expression (N);
432 Insert_Action (N, Obj_Decl);
433 end Transform_BIP_Assignment;
435 ---------------------
436 -- Within_Function --
437 ---------------------
439 function Within_Function return Boolean is
440 Scop_Id : constant Entity_Id := Current_Scope;
442 begin
443 if Ekind (Scop_Id) = E_Function then
444 return True;
446 elsif Ekind (Enclosing_Dynamic_Scope (Scop_Id)) = E_Function then
447 return True;
448 end if;
450 return False;
451 end Within_Function;
453 -- Local variables
455 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
456 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
457 -- Save the Ghost-related attributes to restore on exit
459 T1 : Entity_Id;
460 T2 : Entity_Id;
462 Save_Full_Analysis : Boolean := False;
463 -- Force initialization to facilitate static analysis
465 -- Start of processing for Analyze_Assignment
467 begin
468 Mark_Coextensions (N, Rhs);
470 -- Preserve relevant elaboration-related attributes of the context which
471 -- are no longer available or very expensive to recompute once analysis,
472 -- resolution, and expansion are over.
474 Mark_Elaboration_Attributes
475 (N_Id => N,
476 Checks => True,
477 Modes => True);
479 -- An assignment statement is Ghost when the left hand side denotes a
480 -- Ghost entity. Set the mode now to ensure that any nodes generated
481 -- during analysis and expansion are properly marked as Ghost.
483 Mark_And_Set_Ghost_Assignment (N);
485 if Has_Target_Names (N) then
486 pragma Assert (No (Current_Assignment));
487 Current_Assignment := N;
488 Expander_Mode_Save_And_Set (False);
489 Save_Full_Analysis := Full_Analysis;
490 Full_Analysis := False;
491 end if;
493 Analyze (Lhs);
494 Analyze (Rhs);
496 -- Ensure that we never do an assignment on a variable marked as
497 -- Is_Safe_To_Reevaluate.
499 pragma Assert
500 (not Is_Entity_Name (Lhs)
501 or else Ekind (Entity (Lhs)) /= E_Variable
502 or else not Is_Safe_To_Reevaluate (Entity (Lhs)));
504 -- Start type analysis for assignment
506 T1 := Etype (Lhs);
508 -- In the most general case, both Lhs and Rhs can be overloaded, and we
509 -- must compute the intersection of the possible types on each side.
511 if Is_Overloaded (Lhs) then
512 declare
513 I : Interp_Index;
514 It : Interp;
516 begin
517 T1 := Any_Type;
518 Get_First_Interp (Lhs, I, It);
520 while Present (It.Typ) loop
522 -- An indexed component with generalized indexing is always
523 -- overloaded with the corresponding dereference. Discard the
524 -- interpretation that yields a reference type, which is not
525 -- assignable.
527 if Nkind (Lhs) = N_Indexed_Component
528 and then Present (Generalized_Indexing (Lhs))
529 and then Has_Implicit_Dereference (It.Typ)
530 then
531 null;
533 -- This may be a call to a parameterless function through an
534 -- implicit dereference, so discard interpretation as well.
536 elsif Is_Entity_Name (Lhs)
537 and then Has_Implicit_Dereference (It.Typ)
538 then
539 null;
541 elsif Has_Compatible_Type (Rhs, It.Typ) then
542 if T1 = Any_Type then
543 T1 := It.Typ;
544 else
545 -- An explicit dereference is overloaded if the prefix
546 -- is. Try to remove the ambiguity on the prefix, the
547 -- error will be posted there if the ambiguity is real.
549 if Nkind (Lhs) = N_Explicit_Dereference then
550 declare
551 PI : Interp_Index;
552 PI1 : Interp_Index := 0;
553 PIt : Interp;
554 Found : Boolean;
556 begin
557 Found := False;
558 Get_First_Interp (Prefix (Lhs), PI, PIt);
560 while Present (PIt.Typ) loop
561 if Is_Access_Type (PIt.Typ)
562 and then Has_Compatible_Type
563 (Rhs, Designated_Type (PIt.Typ))
564 then
565 if Found then
566 PIt :=
567 Disambiguate (Prefix (Lhs),
568 PI1, PI, Any_Type);
570 if PIt = No_Interp then
571 Error_Msg_N
572 ("ambiguous left-hand side in "
573 & "assignment", Lhs);
574 exit;
575 else
576 Resolve (Prefix (Lhs), PIt.Typ);
577 end if;
579 exit;
580 else
581 Found := True;
582 PI1 := PI;
583 end if;
584 end if;
586 Get_Next_Interp (PI, PIt);
587 end loop;
588 end;
590 else
591 Error_Msg_N
592 ("ambiguous left-hand side in assignment", Lhs);
593 exit;
594 end if;
595 end if;
596 end if;
598 Get_Next_Interp (I, It);
599 end loop;
600 end;
602 if T1 = Any_Type then
603 Error_Msg_N
604 ("no valid types for left-hand side for assignment", Lhs);
605 Kill_Lhs;
606 goto Leave;
607 end if;
608 end if;
610 -- Deal with build-in-place calls for nonlimited types. We don't do this
611 -- later, because resolving the rhs tranforms it incorrectly for build-
612 -- in-place.
614 if Should_Transform_BIP_Assignment (Typ => T1) then
616 -- In certain cases involving user-defined concatenation operators,
617 -- we need to resolve the right-hand side before transforming the
618 -- assignment.
620 case Nkind (Unqual_Conv (Rhs)) is
621 when N_Function_Call =>
622 declare
623 Actual : Node_Id :=
624 First (Parameter_Associations (Unqual_Conv (Rhs)));
625 Actual_Exp : Node_Id;
627 begin
628 while Present (Actual) loop
629 if Nkind (Actual) = N_Parameter_Association then
630 Actual_Exp := Explicit_Actual_Parameter (Actual);
631 else
632 Actual_Exp := Actual;
633 end if;
635 if Nkind (Actual_Exp) = N_Op_Concat then
636 Resolve (Rhs, T1);
637 exit;
638 end if;
640 Next (Actual);
641 end loop;
642 end;
644 when N_Attribute_Reference
645 | N_Expanded_Name
646 | N_Identifier
647 | N_Op
649 null;
651 when others =>
652 raise Program_Error;
653 end case;
655 Transform_BIP_Assignment (Typ => T1);
656 end if;
658 pragma Assert (not Should_Transform_BIP_Assignment (Typ => T1));
660 -- The resulting assignment type is T1, so now we will resolve the left
661 -- hand side of the assignment using this determined type.
663 Resolve (Lhs, T1);
665 -- Cases where Lhs is not a variable. In an instance or an inlined body
666 -- no need for further check because assignment was legal in template.
668 if In_Inlined_Body then
669 null;
671 elsif not Is_Variable (Lhs) then
673 -- Ada 2005 (AI-327): Check assignment to the attribute Priority of a
674 -- protected object.
676 declare
677 Ent : Entity_Id;
678 S : Entity_Id;
680 begin
681 if Ada_Version >= Ada_2005 then
683 -- Handle chains of renamings
685 Ent := Lhs;
686 while Nkind (Ent) in N_Has_Entity
687 and then Present (Entity (Ent))
688 and then Is_Object (Entity (Ent))
689 and then Present (Renamed_Object (Entity (Ent)))
690 loop
691 Ent := Renamed_Object (Entity (Ent));
692 end loop;
694 if (Nkind (Ent) = N_Attribute_Reference
695 and then Attribute_Name (Ent) = Name_Priority)
697 -- Renamings of the attribute Priority applied to protected
698 -- objects have been previously expanded into calls to the
699 -- Get_Ceiling run-time subprogram.
701 or else Is_Expanded_Priority_Attribute (Ent)
702 then
703 -- The enclosing subprogram cannot be a protected function
705 S := Current_Scope;
706 while not (Is_Subprogram (S)
707 and then Convention (S) = Convention_Protected)
708 and then S /= Standard_Standard
709 loop
710 S := Scope (S);
711 end loop;
713 if Ekind (S) = E_Function
714 and then Convention (S) = Convention_Protected
715 then
716 Error_Msg_N
717 ("protected function cannot modify its protected " &
718 "object",
719 Lhs);
720 end if;
722 -- Changes of the ceiling priority of the protected object
723 -- are only effective if the Ceiling_Locking policy is in
724 -- effect (AARM D.5.2 (5/2)).
726 if Locking_Policy /= 'C' then
727 Error_Msg_N
728 ("assignment to the attribute PRIORITY has no effect??",
729 Lhs);
730 Error_Msg_N
731 ("\since no Locking_Policy has been specified??", Lhs);
732 end if;
734 goto Leave;
735 end if;
736 end if;
737 end;
739 Diagnose_Non_Variable_Lhs (Lhs);
740 goto Leave;
742 -- Error of assigning to limited type. We do however allow this in
743 -- certain cases where the front end generates the assignments.
745 elsif Is_Limited_Type (T1)
746 and then not Assignment_OK (Lhs)
747 and then not Assignment_OK (Original_Node (Lhs))
748 then
749 -- CPP constructors can only be called in declarations
751 if Is_CPP_Constructor_Call (Rhs) then
752 Error_Msg_N ("invalid use of 'C'P'P constructor", Rhs);
753 else
754 Error_Msg_N
755 ("left hand of assignment must not be limited type", Lhs);
756 Explain_Limited_Type (T1, Lhs);
757 end if;
759 goto Leave;
761 -- A class-wide type may be a limited view. This illegal case is not
762 -- caught by previous checks.
764 elsif Ekind (T1) = E_Class_Wide_Type and then From_Limited_With (T1) then
765 Error_Msg_NE ("invalid use of limited view of&", Lhs, T1);
766 goto Leave;
768 -- Enforce RM 3.9.3 (8): the target of an assignment operation cannot be
769 -- abstract. This is only checked when the assignment Comes_From_Source,
770 -- because in some cases the expander generates such assignments (such
771 -- in the _assign operation for an abstract type).
773 elsif Is_Abstract_Type (T1) and then Comes_From_Source (N) then
774 Error_Msg_N
775 ("target of assignment operation must not be abstract", Lhs);
776 end if;
778 -- Variables which are Part_Of constituents of single protected types
779 -- behave in similar fashion to protected components. Such variables
780 -- cannot be modified by protected functions.
782 if Is_Protected_Part_Of_Constituent (Lhs) and then Within_Function then
783 Error_Msg_N
784 ("protected function cannot modify its protected object", Lhs);
785 end if;
787 -- Resolution may have updated the subtype, in case the left-hand side
788 -- is a private protected component. Use the correct subtype to avoid
789 -- scoping issues in the back-end.
791 T1 := Etype (Lhs);
793 -- Ada 2005 (AI-50217, AI-326): Check wrong dereference of incomplete
794 -- type. For example:
796 -- limited with P;
797 -- package Pkg is
798 -- type Acc is access P.T;
799 -- end Pkg;
801 -- with Pkg; use Acc;
802 -- procedure Example is
803 -- A, B : Acc;
804 -- begin
805 -- A.all := B.all; -- ERROR
806 -- end Example;
808 if Nkind (Lhs) = N_Explicit_Dereference
809 and then Ekind (T1) = E_Incomplete_Type
810 then
811 Error_Msg_N ("invalid use of incomplete type", Lhs);
812 Kill_Lhs;
813 goto Leave;
814 end if;
816 -- Now we can complete the resolution of the right hand side
818 Set_Assignment_Type (Lhs, T1);
820 -- If the target of the assignment is an entity of a mutable type and
821 -- the expression is a conditional expression, its alternatives can be
822 -- of different subtypes of the nominal type of the LHS, so they must be
823 -- resolved with the base type, given that their subtype may differ from
824 -- that of the target mutable object.
826 if Is_Entity_Name (Lhs)
827 and then Is_Assignable (Entity (Lhs))
828 and then Is_Composite_Type (T1)
829 and then not Is_Constrained (Etype (Entity (Lhs)))
830 and then Nkind (Rhs) in N_If_Expression | N_Case_Expression
831 then
832 Resolve (Rhs, Base_Type (T1));
834 else
835 Resolve (Rhs, T1);
836 end if;
838 -- This is the point at which we check for an unset reference
840 Check_Unset_Reference (Rhs);
841 Check_Unprotected_Access (Lhs, Rhs);
843 -- Remaining steps are skipped if Rhs was syntactically in error
845 if Rhs = Error then
846 Kill_Lhs;
847 goto Leave;
848 end if;
850 T2 := Etype (Rhs);
852 if not Covers (T1, T2) then
853 Wrong_Type (Rhs, Etype (Lhs));
854 Kill_Lhs;
855 goto Leave;
856 end if;
858 -- Ada 2005 (AI-326): In case of explicit dereference of incomplete
859 -- types, use the non-limited view if available
861 if Nkind (Rhs) = N_Explicit_Dereference
862 and then Is_Tagged_Type (T2)
863 and then Has_Non_Limited_View (T2)
864 then
865 T2 := Non_Limited_View (T2);
866 end if;
868 Set_Assignment_Type (Rhs, T2);
870 if Total_Errors_Detected /= 0 then
871 if No (T1) then
872 T1 := Any_Type;
873 end if;
875 if No (T2) then
876 T2 := Any_Type;
877 end if;
878 end if;
880 if T1 = Any_Type or else T2 = Any_Type then
881 Kill_Lhs;
882 goto Leave;
883 end if;
885 -- If the rhs is class-wide or dynamically tagged, then require the lhs
886 -- to be class-wide. The case where the rhs is a dynamically tagged call
887 -- to a dispatching operation with a controlling access result is
888 -- excluded from this check, since the target has an access type (and
889 -- no tag propagation occurs in that case).
891 if (Is_Class_Wide_Type (T2)
892 or else (Is_Dynamically_Tagged (Rhs)
893 and then not Is_Access_Type (T1)))
894 and then not Is_Class_Wide_Type (T1)
895 then
896 Error_Msg_N ("dynamically tagged expression not allowed!", Rhs);
898 elsif Is_Class_Wide_Type (T1)
899 and then not Is_Class_Wide_Type (T2)
900 and then not Is_Tag_Indeterminate (Rhs)
901 and then not Is_Dynamically_Tagged (Rhs)
902 then
903 Error_Msg_N ("dynamically tagged expression required!", Rhs);
904 end if;
906 -- Propagate the tag from a class-wide target to the rhs when the rhs
907 -- is a tag-indeterminate call.
909 if Is_Tag_Indeterminate (Rhs) then
910 if Is_Class_Wide_Type (T1) then
911 Propagate_Tag (Lhs, Rhs);
913 elsif Nkind (Rhs) = N_Function_Call
914 and then Is_Entity_Name (Name (Rhs))
915 and then Is_Abstract_Subprogram (Entity (Name (Rhs)))
916 then
917 Error_Msg_N
918 ("call to abstract function must be dispatching", Name (Rhs));
920 elsif Nkind (Rhs) = N_Qualified_Expression
921 and then Nkind (Expression (Rhs)) = N_Function_Call
922 and then Is_Entity_Name (Name (Expression (Rhs)))
923 and then
924 Is_Abstract_Subprogram (Entity (Name (Expression (Rhs))))
925 then
926 Error_Msg_N
927 ("call to abstract function must be dispatching",
928 Name (Expression (Rhs)));
929 end if;
930 end if;
932 -- Ada 2005 (AI-385): When the lhs type is an anonymous access type,
933 -- apply an implicit conversion of the rhs to that type to force
934 -- appropriate static and run-time accessibility checks. This applies
935 -- as well to anonymous access-to-subprogram types that are component
936 -- subtypes or formal parameters.
938 if Ada_Version >= Ada_2005 and then Is_Access_Type (T1) then
939 if Is_Local_Anonymous_Access (T1)
940 or else Ekind (T2) = E_Anonymous_Access_Subprogram_Type
942 -- Handle assignment to an Ada 2012 stand-alone object
943 -- of an anonymous access type.
945 or else (Ekind (T1) = E_Anonymous_Access_Type
946 and then Nkind (Associated_Node_For_Itype (T1)) =
947 N_Object_Declaration)
949 then
950 Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
951 Analyze_And_Resolve (Rhs, T1);
952 end if;
953 end if;
955 -- Ada 2005 (AI-231): Assignment to not null variable
957 if Ada_Version >= Ada_2005
958 and then Can_Never_Be_Null (T1)
959 and then not Assignment_OK (Lhs)
960 then
961 -- Case where we know the right hand side is null
963 if Known_Null (Rhs) then
964 Apply_Compile_Time_Constraint_Error
965 (N => Rhs,
966 Msg =>
967 "(Ada 2005) NULL not allowed in null-excluding objects??",
968 Reason => CE_Null_Not_Allowed);
970 -- We still mark this as a possible modification, that's necessary
971 -- to reset Is_True_Constant, and desirable for xref purposes.
973 Note_Possible_Modification (Lhs, Sure => True);
974 goto Leave;
976 -- If we know the right hand side is non-null, then we convert to the
977 -- target type, since we don't need a run time check in that case.
979 elsif not Can_Never_Be_Null (T2) then
980 Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
981 Analyze_And_Resolve (Rhs, T1);
982 end if;
983 end if;
985 if Is_Scalar_Type (T1) then
986 declare
988 function Omit_Range_Check_For_Streaming return Boolean;
989 -- Return True if this assignment statement is the expansion of
990 -- a Some_Scalar_Type'Read procedure call such that all conditions
991 -- of 13.3.2(35)'s "no check is made" rule are met.
993 ------------------------------------
994 -- Omit_Range_Check_For_Streaming --
995 ------------------------------------
997 function Omit_Range_Check_For_Streaming return Boolean is
998 begin
999 -- Have we got an implicitly generated assignment to a
1000 -- component of a composite object? If not, return False.
1002 if Comes_From_Source (N)
1003 or else Serious_Errors_Detected > 0
1004 or else Nkind (Lhs)
1005 not in N_Selected_Component | N_Indexed_Component
1006 then
1007 return False;
1008 end if;
1010 declare
1011 Pref : constant Node_Id := Prefix (Lhs);
1012 begin
1013 -- Are we in the implicitly-defined Read subprogram
1014 -- for a composite type, reading the value of a scalar
1015 -- component from the stream? If not, return False.
1017 if Nkind (Pref) /= N_Identifier
1018 or else not Is_TSS (Scope (Entity (Pref)), TSS_Stream_Read)
1019 then
1020 return False;
1021 end if;
1023 -- Return False if Default_Value or Default_Component_Value
1024 -- aspect applies.
1026 if Has_Default_Aspect (Etype (Lhs))
1027 or else Has_Default_Aspect (Etype (Pref))
1028 then
1029 return False;
1031 -- Are we assigning to a record component (as opposed to
1032 -- an array component)?
1034 elsif Nkind (Lhs) = N_Selected_Component then
1036 -- Are we assigning to a nondiscriminant component
1037 -- that lacks a default initial value expression?
1038 -- If so, return True.
1040 declare
1041 Comp_Id : constant Entity_Id :=
1042 Original_Record_Component
1043 (Entity (Selector_Name (Lhs)));
1044 begin
1045 if Ekind (Comp_Id) = E_Component
1046 and then Nkind (Parent (Comp_Id))
1047 = N_Component_Declaration
1048 and then No (Expression (Parent (Comp_Id)))
1049 then
1050 return True;
1051 end if;
1052 return False;
1053 end;
1055 -- We are assigning to a component of an array
1056 -- (and we tested for both Default_Value and
1057 -- Default_Component_Value above), so return True.
1059 else
1060 pragma Assert (Nkind (Lhs) = N_Indexed_Component);
1061 return True;
1062 end if;
1063 end;
1064 end Omit_Range_Check_For_Streaming;
1066 begin
1067 if not Omit_Range_Check_For_Streaming then
1068 Apply_Scalar_Range_Check (Rhs, Etype (Lhs));
1069 end if;
1070 end;
1072 -- For array types, verify that lengths match. If the right hand side
1073 -- is a function call that has been inlined, the assignment has been
1074 -- rewritten as a block, and the constraint check will be applied to the
1075 -- assignment within the block.
1077 elsif Is_Array_Type (T1)
1078 and then (Nkind (Rhs) /= N_Type_Conversion
1079 or else Is_Constrained (Etype (Rhs)))
1080 and then (Nkind (Rhs) /= N_Function_Call
1081 or else Nkind (N) /= N_Block_Statement)
1082 then
1083 -- Assignment verifies that the length of the Lhs and Rhs are equal,
1084 -- but of course the indexes do not have to match. If the right-hand
1085 -- side is a type conversion to an unconstrained type, a length check
1086 -- is performed on the expression itself during expansion. In rare
1087 -- cases, the redundant length check is computed on an index type
1088 -- with a different representation, triggering incorrect code in the
1089 -- back end.
1091 Apply_Length_Check_On_Assignment (Rhs, Etype (Lhs), Lhs);
1093 else
1094 -- Discriminant checks are applied in the course of expansion
1096 null;
1097 end if;
1099 -- Note: modifications of the Lhs may only be recorded after
1100 -- checks have been applied.
1102 Note_Possible_Modification (Lhs, Sure => True);
1104 -- ??? a real accessibility check is needed when ???
1106 -- Post warning for redundant assignment or variable to itself
1108 if Warn_On_Redundant_Constructs
1110 -- We only warn for source constructs
1112 and then Comes_From_Source (N)
1114 -- Where the object is the same on both sides
1116 and then Same_Object (Lhs, Rhs)
1118 -- But exclude the case where the right side was an operation that
1119 -- got rewritten (e.g. JUNK + K, where K was known to be zero). We
1120 -- don't want to warn in such a case, since it is reasonable to write
1121 -- such expressions especially when K is defined symbolically in some
1122 -- other package.
1124 and then Nkind (Original_Node (Rhs)) not in N_Op
1125 then
1126 if Nkind (Lhs) in N_Has_Entity then
1127 Error_Msg_NE -- CODEFIX
1128 ("?r?useless assignment of & to itself!", N, Entity (Lhs));
1129 else
1130 Error_Msg_N -- CODEFIX
1131 ("?r?useless assignment of object to itself!", N);
1132 end if;
1133 end if;
1135 -- Check for non-allowed composite assignment
1137 if not Support_Composite_Assign_On_Target
1138 and then (Is_Array_Type (T1) or else Is_Record_Type (T1))
1139 and then (not Has_Size_Clause (T1)
1140 or else Esize (T1) > Ttypes.System_Max_Integer_Size)
1141 then
1142 Error_Msg_CRT ("composite assignment", N);
1143 end if;
1145 -- Check elaboration warning for left side if not in elab code
1147 if Legacy_Elaboration_Checks
1148 and not In_Subprogram_Or_Concurrent_Unit
1149 then
1150 Check_Elab_Assign (Lhs);
1151 end if;
1153 -- Save the scenario for later examination by the ABE Processing phase
1155 Record_Elaboration_Scenario (N);
1157 -- Set Referenced_As_LHS if appropriate. We are not interested in
1158 -- compiler-generated assignment statements, nor in references outside
1159 -- the extended main source unit. We check whether the Original_Node is
1160 -- in the extended main source unit because in the case of a renaming of
1161 -- a component of a packed array, the Lhs itself has a Sloc from the
1162 -- place of the renaming.
1164 if Comes_From_Source (N)
1165 and then (In_Extended_Main_Source_Unit (Lhs)
1166 or else In_Extended_Main_Source_Unit (Original_Node (Lhs)))
1167 then
1168 Set_Referenced_Modified (Lhs, Out_Param => False);
1169 end if;
1171 -- RM 7.3.2 (12/3): An assignment to a view conversion (from a type to
1172 -- one of its ancestors) requires an invariant check. Apply check only
1173 -- if expression comes from source, otherwise it will be applied when
1174 -- value is assigned to source entity. This is not done in GNATprove
1175 -- mode, as GNATprove handles invariant checks itself.
1177 if Nkind (Lhs) = N_Type_Conversion
1178 and then Has_Invariants (Etype (Expression (Lhs)))
1179 and then Comes_From_Source (Expression (Lhs))
1180 and then not GNATprove_Mode
1181 then
1182 Insert_After (N, Make_Invariant_Call (Expression (Lhs)));
1183 end if;
1185 -- Final step. If left side is an entity, then we may be able to reset
1186 -- the current tracked values to new safe values. We only have something
1187 -- to do if the left side is an entity name, and expansion has not
1188 -- modified the node into something other than an assignment, and of
1189 -- course we only capture values if it is safe to do so.
1191 if Is_Entity_Name (Lhs)
1192 and then Nkind (N) = N_Assignment_Statement
1193 then
1194 declare
1195 Ent : constant Entity_Id := Entity (Lhs);
1197 begin
1198 if Safe_To_Capture_Value (N, Ent) then
1200 -- If simple variable on left side, warn if this assignment
1201 -- blots out another one (rendering it useless). We only do
1202 -- this for source assignments, otherwise we can generate bogus
1203 -- warnings when an assignment is rewritten as another
1204 -- assignment, and gets tied up with itself.
1206 -- We also omit the warning if the RHS includes target names,
1207 -- that is to say the Ada 2022 "@" that denotes an instance of
1208 -- the LHS, which indicates that the current value is being
1209 -- used. Note that this implicit reference to the entity on
1210 -- the RHS is not treated as a source reference.
1212 -- There may have been a previous reference to a component of
1213 -- the variable, which in general removes the Last_Assignment
1214 -- field of the variable to indicate a relevant use of the
1215 -- previous assignment.
1217 if Warn_On_Modified_Unread
1218 and then Is_Assignable (Ent)
1219 and then Comes_From_Source (N)
1220 and then In_Extended_Main_Source_Unit (Ent)
1221 and then not Has_Target_Names (N)
1222 then
1223 Warn_On_Useless_Assignment (Ent, N);
1224 end if;
1226 -- If we are assigning an access type and the left side is an
1227 -- entity, then make sure that the Is_Known_[Non_]Null flags
1228 -- properly reflect the state of the entity after assignment.
1230 if Is_Access_Type (T1) then
1231 if Known_Non_Null (Rhs) then
1232 Set_Is_Known_Non_Null (Ent, True);
1234 elsif Known_Null (Rhs)
1235 and then not Can_Never_Be_Null (Ent)
1236 then
1237 Set_Is_Known_Null (Ent, True);
1239 else
1240 Set_Is_Known_Null (Ent, False);
1242 if not Can_Never_Be_Null (Ent) then
1243 Set_Is_Known_Non_Null (Ent, False);
1244 end if;
1245 end if;
1247 -- For discrete types, we may be able to set the current value
1248 -- if the value is known at compile time.
1250 elsif Is_Discrete_Type (T1)
1251 and then Compile_Time_Known_Value (Rhs)
1252 then
1253 Set_Current_Value (Ent, Rhs);
1254 else
1255 Set_Current_Value (Ent, Empty);
1256 end if;
1258 -- If not safe to capture values, kill them
1260 else
1261 Kill_Lhs;
1262 end if;
1263 end;
1264 end if;
1266 -- If assigning to an object in whole or in part, note location of
1267 -- assignment in case no one references value. We only do this for
1268 -- source assignments, otherwise we can generate bogus warnings when an
1269 -- assignment is rewritten as another assignment, and gets tied up with
1270 -- itself.
1272 declare
1273 Ent : constant Entity_Id := Get_Enclosing_Object (Lhs);
1274 begin
1275 if Present (Ent)
1276 and then Safe_To_Capture_Value (N, Ent)
1277 and then Nkind (N) = N_Assignment_Statement
1278 and then Warn_On_Modified_Unread
1279 and then Is_Assignable (Ent)
1280 and then Comes_From_Source (N)
1281 and then In_Extended_Main_Source_Unit (Ent)
1282 then
1283 Set_Last_Assignment (Ent, Lhs);
1284 end if;
1285 end;
1287 Analyze_Dimension (N);
1289 <<Leave>>
1290 Restore_Ghost_Region (Saved_GM, Saved_IGR);
1292 -- If the right-hand side contains target names, expansion has been
1293 -- disabled to prevent expansion that might move target names out of
1294 -- the context of the assignment statement. Restore the expander mode
1295 -- now so that assignment statement can be properly expanded.
1297 if Nkind (N) = N_Assignment_Statement then
1298 if Has_Target_Names (N) then
1299 Expander_Mode_Restore;
1300 Full_Analysis := Save_Full_Analysis;
1301 Current_Assignment := Empty;
1302 end if;
1304 pragma Assert (not Should_Transform_BIP_Assignment (Typ => T1));
1305 end if;
1306 end Analyze_Assignment;
1308 -----------------------------
1309 -- Analyze_Block_Statement --
1310 -----------------------------
1312 procedure Analyze_Block_Statement (N : Node_Id) is
1313 procedure Install_Return_Entities (Scop : Entity_Id);
1314 -- Install all entities of return statement scope Scop in the visibility
1315 -- chain except for the return object since its entity is reused in a
1316 -- renaming.
1318 -----------------------------
1319 -- Install_Return_Entities --
1320 -----------------------------
1322 procedure Install_Return_Entities (Scop : Entity_Id) is
1323 Id : Entity_Id;
1325 begin
1326 Id := First_Entity (Scop);
1327 while Present (Id) loop
1329 -- Do not install the return object
1331 if Ekind (Id) not in E_Constant | E_Variable
1332 or else not Is_Return_Object (Id)
1333 then
1334 Install_Entity (Id);
1335 end if;
1337 Next_Entity (Id);
1338 end loop;
1339 end Install_Return_Entities;
1341 -- Local constants and variables
1343 Decls : constant List_Id := Declarations (N);
1344 Id : constant Node_Id := Identifier (N);
1345 HSS : constant Node_Id := Handled_Statement_Sequence (N);
1347 Is_BIP_Return_Statement : Boolean;
1349 -- Start of processing for Analyze_Block_Statement
1351 begin
1352 -- If no handled statement sequence is present, things are really messed
1353 -- up, and we just return immediately (defence against previous errors).
1355 if No (HSS) then
1356 Check_Error_Detected;
1357 return;
1358 end if;
1360 -- Detect whether the block is actually a rewritten return statement of
1361 -- a build-in-place function.
1363 Is_BIP_Return_Statement :=
1364 Present (Id)
1365 and then Present (Entity (Id))
1366 and then Ekind (Entity (Id)) = E_Return_Statement
1367 and then Is_Build_In_Place_Function
1368 (Return_Applies_To (Entity (Id)));
1370 -- Normal processing with HSS present
1372 declare
1373 EH : constant List_Id := Exception_Handlers (HSS);
1374 Ent : Entity_Id := Empty;
1375 S : Entity_Id;
1377 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1378 -- Recursively save value of this global, will be restored on exit
1380 begin
1381 -- Initialize unblocked exit count for statements of begin block
1382 -- plus one for each exception handler that is present.
1384 Unblocked_Exit_Count := 1 + List_Length (EH);
1386 -- If a label is present analyze it and mark it as referenced
1388 if Present (Id) then
1389 Analyze (Id);
1390 Ent := Entity (Id);
1392 -- An error defense. If we have an identifier, but no entity, then
1393 -- something is wrong. If previous errors, then just remove the
1394 -- identifier and continue, otherwise raise an exception.
1396 if No (Ent) then
1397 Check_Error_Detected;
1398 Set_Identifier (N, Empty);
1400 else
1401 if Ekind (Ent) = E_Label then
1402 Reinit_Field_To_Zero (Ent, F_Enclosing_Scope);
1403 end if;
1405 Mutate_Ekind (Ent, E_Block);
1406 Generate_Reference (Ent, N, ' ');
1407 Generate_Definition (Ent);
1409 if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
1410 Set_Label_Construct (Parent (Ent), N);
1411 end if;
1412 end if;
1413 end if;
1415 -- If no entity set, create a label entity
1417 if No (Ent) then
1418 Ent := New_Internal_Entity (E_Block, Current_Scope, Sloc (N), 'B');
1419 Set_Identifier (N, New_Occurrence_Of (Ent, Sloc (N)));
1420 Set_Parent (Ent, N);
1421 end if;
1423 Set_Etype (Ent, Standard_Void_Type);
1424 Set_Block_Node (Ent, Identifier (N));
1425 Push_Scope (Ent);
1427 -- The block served as an extended return statement. Ensure that any
1428 -- entities created during the analysis and expansion of the return
1429 -- object declaration are once again visible.
1431 if Is_BIP_Return_Statement then
1432 Install_Return_Entities (Ent);
1433 end if;
1435 if Present (Decls) then
1436 Analyze_Declarations (Decls);
1437 Check_Completion;
1438 Inspect_Deferred_Constant_Completion (Decls);
1439 end if;
1441 Analyze (HSS);
1442 Process_End_Label (HSS, 'e', Ent);
1444 -- If exception handlers are present, then we indicate that enclosing
1445 -- scopes contain a block with handlers. We only need to mark non-
1446 -- generic scopes.
1448 if Present (EH) then
1449 S := Scope (Ent);
1450 loop
1451 Set_Has_Nested_Block_With_Handler (S);
1452 exit when Is_Overloadable (S)
1453 or else Ekind (S) = E_Package
1454 or else Is_Generic_Unit (S);
1455 S := Scope (S);
1456 end loop;
1457 end if;
1459 Check_References (Ent);
1460 Update_Use_Clause_Chain;
1461 End_Scope;
1463 if Unblocked_Exit_Count = 0 then
1464 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1465 Check_Unreachable_Code (N);
1466 else
1467 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1468 end if;
1469 end;
1470 end Analyze_Block_Statement;
1472 --------------------------------
1473 -- Analyze_Compound_Statement --
1474 --------------------------------
1476 procedure Analyze_Compound_Statement (N : Node_Id) is
1477 begin
1478 Analyze_List (Actions (N));
1479 end Analyze_Compound_Statement;
1481 ----------------------------
1482 -- Analyze_Case_Statement --
1483 ----------------------------
1485 procedure Analyze_Case_Statement (N : Node_Id) is
1486 Exp : constant Node_Id := Expression (N);
1488 Statements_Analyzed : Boolean := False;
1489 -- Set True if at least some statement sequences get analyzed. If False
1490 -- on exit, means we had a serious error that prevented full analysis of
1491 -- the case statement, and as a result it is not a good idea to output
1492 -- warning messages about unreachable code.
1494 Is_General_Case_Statement : Boolean := False;
1495 -- Set True (later) if type of case expression is not discrete
1497 procedure Non_Static_Choice_Error (Choice : Node_Id);
1498 -- Error routine invoked by the generic instantiation below when the
1499 -- case statement has a non static choice.
1501 procedure Process_Statements (Alternative : Node_Id);
1502 -- Analyzes the statements associated with a case alternative. Needed
1503 -- by instantiation below.
1505 package Analyze_Case_Choices is new
1506 Generic_Analyze_Choices
1507 (Process_Associated_Node => Process_Statements);
1508 use Analyze_Case_Choices;
1509 -- Instantiation of the generic choice analysis package
1511 package Check_Case_Choices is new
1512 Generic_Check_Choices
1513 (Process_Empty_Choice => No_OP,
1514 Process_Non_Static_Choice => Non_Static_Choice_Error,
1515 Process_Associated_Node => No_OP);
1516 use Check_Case_Choices;
1517 -- Instantiation of the generic choice processing package
1519 -----------------------------
1520 -- Non_Static_Choice_Error --
1521 -----------------------------
1523 procedure Non_Static_Choice_Error (Choice : Node_Id) is
1524 begin
1525 Flag_Non_Static_Expr
1526 ("choice given in case statement is not static!", Choice);
1527 end Non_Static_Choice_Error;
1529 ------------------------
1530 -- Process_Statements --
1531 ------------------------
1533 procedure Process_Statements (Alternative : Node_Id) is
1534 Choices : constant List_Id := Discrete_Choices (Alternative);
1535 Ent : Entity_Id;
1537 begin
1538 if Is_General_Case_Statement then
1539 return;
1540 -- Processing deferred in this case; decls associated with
1541 -- pattern match bindings don't exist yet.
1542 end if;
1544 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1545 Statements_Analyzed := True;
1547 -- An interesting optimization. If the case statement expression
1548 -- is a simple entity, then we can set the current value within an
1549 -- alternative if the alternative has one possible value.
1551 -- case N is
1552 -- when 1 => alpha
1553 -- when 2 | 3 => beta
1554 -- when others => gamma
1556 -- Here we know that N is initially 1 within alpha, but for beta and
1557 -- gamma, we do not know anything more about the initial value.
1559 if Is_Entity_Name (Exp) then
1560 Ent := Entity (Exp);
1562 if Is_Object (Ent) then
1563 if List_Length (Choices) = 1
1564 and then Nkind (First (Choices)) in N_Subexpr
1565 and then Compile_Time_Known_Value (First (Choices))
1566 then
1567 Set_Current_Value (Entity (Exp), First (Choices));
1568 end if;
1570 Analyze_Statements (Statements (Alternative));
1572 -- After analyzing the case, set the current value to empty
1573 -- since we won't know what it is for the next alternative
1574 -- (unless reset by this same circuit), or after the case.
1576 Set_Current_Value (Entity (Exp), Empty);
1577 return;
1578 end if;
1579 end if;
1581 -- Case where expression is not an entity name of an object
1583 Analyze_Statements (Statements (Alternative));
1584 end Process_Statements;
1586 -- Local variables
1588 Exp_Type : Entity_Id;
1589 Exp_Btype : Entity_Id;
1591 Others_Present : Boolean;
1592 -- Indicates if Others was present
1594 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1595 -- Recursively save value of this global, will be restored on exit
1597 -- Start of processing for Analyze_Case_Statement
1599 begin
1600 Analyze (Exp);
1602 -- The expression must be of any discrete type. In rare cases, the
1603 -- expander constructs a case statement whose expression has a private
1604 -- type whose full view is discrete. This can happen when generating
1605 -- a stream operation for a variant type after the type is frozen,
1606 -- when the partial of view of the type of the discriminant is private.
1607 -- In that case, use the full view to analyze case alternatives.
1609 if not Is_Overloaded (Exp)
1610 and then not Comes_From_Source (N)
1611 and then Is_Private_Type (Etype (Exp))
1612 and then Present (Full_View (Etype (Exp)))
1613 and then Is_Discrete_Type (Full_View (Etype (Exp)))
1614 then
1615 Resolve (Exp);
1616 Exp_Type := Full_View (Etype (Exp));
1618 -- For Ada, overloading might be ok because subsequently filtering
1619 -- out non-discretes may resolve the ambiguity.
1620 -- But GNAT extensions allow casing on non-discretes.
1622 elsif Core_Extensions_Allowed and then Is_Overloaded (Exp) then
1624 -- It would be nice if we could generate all the right error
1625 -- messages by calling "Resolve (Exp, Any_Type);" in the
1626 -- same way that they are generated a few lines below by the
1627 -- call "Analyze_And_Resolve (Exp, Any_Discrete);".
1628 -- Unfortunately, Any_Type and Any_Discrete are not treated
1629 -- consistently (specifically, by Sem_Type.Covers), so that
1630 -- doesn't work.
1632 Error_Msg_N
1633 ("selecting expression of general case statement is ambiguous",
1634 Exp);
1635 return;
1637 -- Check for a GNAT-extension "general" case statement (i.e., one where
1638 -- the type of the selecting expression is not discrete).
1640 elsif Core_Extensions_Allowed
1641 and then not Is_Discrete_Type (Etype (Exp))
1642 then
1643 Resolve (Exp, Etype (Exp));
1644 Exp_Type := Etype (Exp);
1645 Is_General_Case_Statement := True;
1646 else
1647 Analyze_And_Resolve (Exp, Any_Discrete);
1648 Exp_Type := Etype (Exp);
1649 end if;
1651 Check_Unset_Reference (Exp);
1652 Exp_Btype := Base_Type (Exp_Type);
1654 -- The expression must be of a discrete type which must be determinable
1655 -- independently of the context in which the expression occurs, but
1656 -- using the fact that the expression must be of a discrete type.
1657 -- Moreover, the type this expression must not be a character literal
1658 -- (which is always ambiguous) or, for Ada-83, a generic formal type.
1660 -- If error already reported by Resolve, nothing more to do
1662 if Exp_Btype = Any_Discrete or else Exp_Btype = Any_Type then
1663 return;
1665 elsif Exp_Btype = Any_Character then
1666 Error_Msg_N
1667 ("character literal as case expression is ambiguous", Exp);
1668 return;
1670 elsif Ada_Version = Ada_83
1671 and then (Is_Generic_Type (Exp_Btype)
1672 or else Is_Generic_Type (Root_Type (Exp_Btype)))
1673 then
1674 Error_Msg_N
1675 ("(Ada 83) case expression cannot be of a generic type", Exp);
1676 return;
1678 elsif not Core_Extensions_Allowed
1679 and then not Is_Discrete_Type (Exp_Type)
1680 then
1681 Error_Msg_N
1682 ("expression in case statement must be of a discrete_Type", Exp);
1683 return;
1684 end if;
1686 -- If the case expression is a formal object of mode in out, then treat
1687 -- it as having a nonstatic subtype by forcing use of the base type
1688 -- (which has to get passed to Check_Case_Choices below). Also use base
1689 -- type when the case expression is parenthesized.
1691 if Paren_Count (Exp) > 0
1692 or else (Is_Entity_Name (Exp)
1693 and then Ekind (Entity (Exp)) = E_Generic_In_Out_Parameter)
1694 then
1695 Exp_Type := Exp_Btype;
1696 end if;
1698 -- Call instantiated procedures to analyze and check discrete choices
1700 Unblocked_Exit_Count := 0;
1702 Analyze_Choices (Alternatives (N), Exp_Type);
1703 Check_Choices (N, Alternatives (N), Exp_Type, Others_Present);
1705 if Is_General_Case_Statement then
1706 -- Work normally done in Process_Statements was deferred; do that
1707 -- deferred work now that Check_Choices has had a chance to create
1708 -- any needed pattern-match-binding declarations.
1709 declare
1710 Alt : Node_Id := First (Alternatives (N));
1711 begin
1712 while Present (Alt) loop
1713 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1714 Analyze_Statements (Statements (Alt));
1715 Next (Alt);
1716 end loop;
1717 end;
1718 end if;
1720 if Exp_Type = Universal_Integer and then not Others_Present then
1721 Error_Msg_N ("case on universal integer requires OTHERS choice", Exp);
1722 end if;
1724 -- If all our exits were blocked by unconditional transfers of control,
1725 -- then the entire CASE statement acts as an unconditional transfer of
1726 -- control, so treat it like one, and check unreachable code. Skip this
1727 -- test if we had serious errors preventing any statement analysis.
1729 if Unblocked_Exit_Count = 0 and then Statements_Analyzed then
1730 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1731 Check_Unreachable_Code (N);
1732 else
1733 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1734 end if;
1736 -- If the expander is active it will detect the case of a statically
1737 -- determined single alternative and remove warnings for the case, but
1738 -- if we are not doing expansion, that circuit won't be active. Here we
1739 -- duplicate the effect of removing warnings in the same way, so that
1740 -- we will get the same set of warnings in -gnatc mode.
1742 if not Expander_Active
1743 and then Compile_Time_Known_Value (Expression (N))
1744 and then Serious_Errors_Detected = 0
1745 then
1746 declare
1747 Chosen : constant Node_Id := Find_Static_Alternative (N);
1748 Alt : Node_Id;
1750 begin
1751 Alt := First (Alternatives (N));
1752 while Present (Alt) loop
1753 if Alt /= Chosen then
1754 Remove_Warning_Messages (Statements (Alt));
1755 end if;
1757 Next (Alt);
1758 end loop;
1759 end;
1760 end if;
1761 end Analyze_Case_Statement;
1763 ----------------------------
1764 -- Analyze_Exit_Statement --
1765 ----------------------------
1767 -- If the exit includes a name, it must be the name of a currently open
1768 -- loop. Otherwise there must be an innermost open loop on the stack, to
1769 -- which the statement implicitly refers.
1771 -- Additionally, in SPARK mode:
1773 -- The exit can only name the closest enclosing loop;
1775 -- An exit with a when clause must be directly contained in a loop;
1777 -- An exit without a when clause must be directly contained in an
1778 -- if-statement with no elsif or else, which is itself directly contained
1779 -- in a loop. The exit must be the last statement in the if-statement.
1781 procedure Analyze_Exit_Statement (N : Node_Id) is
1782 Target : constant Node_Id := Name (N);
1783 Cond : constant Node_Id := Condition (N);
1784 Scope_Id : Entity_Id := Empty; -- initialize to prevent warning
1785 U_Name : Entity_Id;
1786 Kind : Entity_Kind;
1788 begin
1789 if No (Cond) then
1790 Check_Unreachable_Code (N);
1791 end if;
1793 if Present (Target) then
1794 Analyze (Target);
1795 U_Name := Entity (Target);
1797 if not In_Open_Scopes (U_Name) or else Ekind (U_Name) /= E_Loop then
1798 Error_Msg_N ("invalid loop name in exit statement", N);
1799 return;
1801 else
1802 Set_Has_Exit (U_Name);
1803 end if;
1805 else
1806 U_Name := Empty;
1807 end if;
1809 for J in reverse 0 .. Scope_Stack.Last loop
1810 Scope_Id := Scope_Stack.Table (J).Entity;
1811 Kind := Ekind (Scope_Id);
1813 if Kind = E_Loop and then (No (Target) or else Scope_Id = U_Name) then
1814 Set_Has_Exit (Scope_Id);
1815 exit;
1817 elsif Kind = E_Block
1818 or else Kind = E_Loop
1819 or else Kind = E_Return_Statement
1820 then
1821 null;
1823 else
1824 Error_Msg_N
1825 ("cannot exit from program unit or accept statement", N);
1826 return;
1827 end if;
1828 end loop;
1830 -- Verify that if present the condition is a Boolean expression
1832 if Present (Cond) then
1833 Analyze_And_Resolve (Cond, Any_Boolean);
1834 Check_Unset_Reference (Cond);
1835 end if;
1837 -- Chain exit statement to associated loop entity
1839 Set_Next_Exit_Statement (N, First_Exit_Statement (Scope_Id));
1840 Set_First_Exit_Statement (Scope_Id, N);
1842 -- Since the exit may take us out of a loop, any previous assignment
1843 -- statement is not useless, so clear last assignment indications. It
1844 -- is OK to keep other current values, since if the exit statement
1845 -- does not exit, then the current values are still valid.
1847 Kill_Current_Values (Last_Assignment_Only => True);
1848 end Analyze_Exit_Statement;
1850 ----------------------------
1851 -- Analyze_Goto_Statement --
1852 ----------------------------
1854 procedure Analyze_Goto_Statement (N : Node_Id) is
1855 Label : constant Node_Id := Name (N);
1856 Scope_Id : Entity_Id;
1857 Label_Scope : Entity_Id;
1858 Label_Ent : Entity_Id;
1860 begin
1861 -- Actual semantic checks
1863 Check_Unreachable_Code (N);
1864 Kill_Current_Values (Last_Assignment_Only => True);
1866 Analyze (Label);
1867 Label_Ent := Entity (Label);
1869 -- Ignore previous error
1871 if Label_Ent = Any_Id then
1872 Check_Error_Detected;
1873 return;
1875 -- We just have a label as the target of a goto
1877 elsif Ekind (Label_Ent) /= E_Label then
1878 Error_Msg_N ("target of goto statement must be a label", Label);
1879 return;
1881 -- Check that the target of the goto is reachable according to Ada
1882 -- scoping rules. Note: the special gotos we generate for optimizing
1883 -- local handling of exceptions would violate these rules, but we mark
1884 -- such gotos as analyzed when built, so this code is never entered.
1886 elsif not Reachable (Label_Ent) then
1887 Error_Msg_N ("target of goto statement is not reachable", Label);
1888 return;
1889 end if;
1891 -- Here if goto passes initial validity checks
1893 Label_Scope := Enclosing_Scope (Label_Ent);
1895 for J in reverse 0 .. Scope_Stack.Last loop
1896 Scope_Id := Scope_Stack.Table (J).Entity;
1898 if Label_Scope = Scope_Id
1899 or else Ekind (Scope_Id) not in
1900 E_Block | E_Loop | E_Return_Statement
1901 then
1902 if Scope_Id /= Label_Scope then
1903 Error_Msg_N
1904 ("cannot exit from program unit or accept statement", N);
1905 end if;
1907 return;
1908 end if;
1909 end loop;
1911 raise Program_Error;
1912 end Analyze_Goto_Statement;
1914 ---------------------------------
1915 -- Analyze_Goto_When_Statement --
1916 ---------------------------------
1918 procedure Analyze_Goto_When_Statement (N : Node_Id) is
1919 begin
1920 -- Verify the condition is a Boolean expression
1922 Analyze_And_Resolve (Condition (N), Any_Boolean);
1923 Check_Unset_Reference (Condition (N));
1924 end Analyze_Goto_When_Statement;
1926 --------------------------
1927 -- Analyze_If_Statement --
1928 --------------------------
1930 -- A special complication arises in the analysis of if statements
1932 -- The expander has circuitry to completely delete code that it can tell
1933 -- will not be executed (as a result of compile time known conditions). In
1934 -- the analyzer, we ensure that code that will be deleted in this manner
1935 -- is analyzed but not expanded. This is obviously more efficient, but
1936 -- more significantly, difficulties arise if code is expanded and then
1937 -- eliminated (e.g. exception table entries disappear). Similarly, itypes
1938 -- generated in deleted code must be frozen from start, because the nodes
1939 -- on which they depend will not be available at the freeze point.
1941 procedure Analyze_If_Statement (N : Node_Id) is
1942 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1943 -- Recursively save value of this global, will be restored on exit
1945 Save_In_Deleted_Code : Boolean := In_Deleted_Code;
1947 Del : Boolean := False;
1948 -- This flag gets set True if a True condition has been found, which
1949 -- means that remaining ELSE/ELSIF parts are deleted.
1951 procedure Analyze_Cond_Then (Cnode : Node_Id);
1952 -- This is applied to either the N_If_Statement node itself or to an
1953 -- N_Elsif_Part node. It deals with analyzing the condition and the THEN
1954 -- statements associated with it.
1956 -----------------------
1957 -- Analyze_Cond_Then --
1958 -----------------------
1960 procedure Analyze_Cond_Then (Cnode : Node_Id) is
1961 Cond : constant Node_Id := Condition (Cnode);
1962 Tstm : constant List_Id := Then_Statements (Cnode);
1964 begin
1965 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1966 Analyze_And_Resolve (Cond, Any_Boolean);
1967 Check_Unset_Reference (Cond);
1968 Set_Current_Value_Condition (Cnode);
1970 -- If already deleting, then just analyze then statements
1972 if Del then
1973 Analyze_Statements (Tstm);
1975 -- Compile time known value, not deleting yet
1977 elsif Compile_Time_Known_Value (Cond) then
1978 Save_In_Deleted_Code := In_Deleted_Code;
1980 -- If condition is True, then analyze the THEN statements and set
1981 -- no expansion for ELSE and ELSIF parts.
1983 if Is_True (Expr_Value (Cond)) then
1984 Analyze_Statements (Tstm);
1985 Del := True;
1986 Expander_Mode_Save_And_Set (False);
1987 In_Deleted_Code := True;
1989 -- If condition is False, analyze THEN with expansion off
1991 else pragma Assert (Is_False (Expr_Value (Cond)));
1992 Expander_Mode_Save_And_Set (False);
1993 In_Deleted_Code := True;
1994 Analyze_Statements (Tstm);
1995 Expander_Mode_Restore;
1996 In_Deleted_Code := Save_In_Deleted_Code;
1997 end if;
1999 -- Not known at compile time, not deleting, normal analysis
2001 else
2002 Analyze_Statements (Tstm);
2003 end if;
2004 end Analyze_Cond_Then;
2006 -- Local variables
2008 E : Node_Id;
2009 -- For iterating over elsif parts
2011 -- Start of processing for Analyze_If_Statement
2013 begin
2014 -- Initialize exit count for else statements. If there is no else part,
2015 -- this count will stay non-zero reflecting the fact that the uncovered
2016 -- else case is an unblocked exit.
2018 Unblocked_Exit_Count := 1;
2019 Analyze_Cond_Then (N);
2021 -- Now to analyze the elsif parts if any are present
2023 E := First (Elsif_Parts (N));
2024 while Present (E) loop
2025 Analyze_Cond_Then (E);
2026 Next (E);
2027 end loop;
2029 if Present (Else_Statements (N)) then
2030 Analyze_Statements (Else_Statements (N));
2031 end if;
2033 -- If all our exits were blocked by unconditional transfers of control,
2034 -- then the entire IF statement acts as an unconditional transfer of
2035 -- control, so treat it like one, and check unreachable code.
2037 if Unblocked_Exit_Count = 0 then
2038 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
2039 Check_Unreachable_Code (N);
2040 else
2041 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
2042 end if;
2044 if Del then
2045 Expander_Mode_Restore;
2046 In_Deleted_Code := Save_In_Deleted_Code;
2047 end if;
2049 if not Expander_Active
2050 and then Compile_Time_Known_Value (Condition (N))
2051 and then Serious_Errors_Detected = 0
2052 then
2053 if Is_True (Expr_Value (Condition (N))) then
2054 Remove_Warning_Messages (Else_Statements (N));
2056 E := First (Elsif_Parts (N));
2057 while Present (E) loop
2058 Remove_Warning_Messages (Then_Statements (E));
2059 Next (E);
2060 end loop;
2062 else
2063 Remove_Warning_Messages (Then_Statements (N));
2064 end if;
2065 end if;
2067 -- Warn on redundant if statement that has no effect
2069 -- Note, we could also check empty ELSIF parts ???
2071 if Warn_On_Redundant_Constructs
2073 -- If statement must be from source
2075 and then Comes_From_Source (N)
2077 -- Condition must not have obvious side effect
2079 and then Has_No_Obvious_Side_Effects (Condition (N))
2081 -- No elsif parts of else part
2083 and then No (Elsif_Parts (N))
2084 and then No (Else_Statements (N))
2086 -- Then must be a single null statement
2088 and then List_Length (Then_Statements (N)) = 1
2089 then
2090 -- Go to original node, since we may have rewritten something as
2091 -- a null statement (e.g. a case we could figure the outcome of).
2093 declare
2094 T : constant Node_Id := First (Then_Statements (N));
2095 S : constant Node_Id := Original_Node (T);
2097 begin
2098 if Comes_From_Source (S) and then Nkind (S) = N_Null_Statement then
2099 Error_Msg_N ("if statement has no effect?r?", N);
2100 end if;
2101 end;
2102 end if;
2103 end Analyze_If_Statement;
2105 ----------------------------------------
2106 -- Analyze_Implicit_Label_Declaration --
2107 ----------------------------------------
2109 -- An implicit label declaration is generated in the innermost enclosing
2110 -- declarative part. This is done for labels, and block and loop names.
2112 procedure Analyze_Implicit_Label_Declaration (N : Node_Id) is
2113 Id : constant Node_Id := Defining_Identifier (N);
2114 begin
2115 Enter_Name (Id);
2116 Mutate_Ekind (Id, E_Label);
2117 Set_Etype (Id, Standard_Void_Type);
2118 Set_Enclosing_Scope (Id, Current_Scope);
2120 -- A label declared within a Ghost region becomes Ghost (SPARK RM
2121 -- 6.9(2)).
2123 if Ghost_Mode > None then
2124 Set_Is_Ghost_Entity (Id);
2125 end if;
2126 end Analyze_Implicit_Label_Declaration;
2128 ------------------------------
2129 -- Analyze_Iteration_Scheme --
2130 ------------------------------
2132 procedure Analyze_Iteration_Scheme (N : Node_Id) is
2133 Cond : Node_Id;
2134 Iter_Spec : Node_Id;
2135 Loop_Spec : Node_Id;
2137 begin
2138 -- For an infinite loop, there is no iteration scheme
2140 if No (N) then
2141 return;
2142 end if;
2144 Cond := Condition (N);
2145 Iter_Spec := Iterator_Specification (N);
2146 Loop_Spec := Loop_Parameter_Specification (N);
2148 if Present (Cond) then
2149 Analyze_And_Resolve (Cond, Any_Boolean);
2150 Check_Unset_Reference (Cond);
2151 Set_Current_Value_Condition (N);
2153 elsif Present (Iter_Spec) then
2154 Analyze_Iterator_Specification (Iter_Spec);
2156 else
2157 Analyze_Loop_Parameter_Specification (Loop_Spec);
2158 end if;
2159 end Analyze_Iteration_Scheme;
2161 ------------------------------------
2162 -- Analyze_Iterator_Specification --
2163 ------------------------------------
2165 procedure Analyze_Iterator_Specification (N : Node_Id) is
2166 Def_Id : constant Node_Id := Defining_Identifier (N);
2167 Iter_Name : constant Node_Id := Name (N);
2168 Loc : constant Source_Ptr := Sloc (N);
2169 Subt : constant Node_Id := Subtype_Indication (N);
2171 Bas : Entity_Id := Empty; -- initialize to prevent warning
2172 Typ : Entity_Id;
2174 procedure Check_Reverse_Iteration (Typ : Entity_Id);
2175 -- For an iteration over a container, if the loop carries the Reverse
2176 -- indicator, verify that the container type has an Iterate aspect that
2177 -- implements the reversible iterator interface.
2179 procedure Check_Subtype_Definition (Comp_Type : Entity_Id);
2180 -- If a subtype indication is present, verify that it is consistent
2181 -- with the component type of the array or container name.
2182 -- In Ada 2022, the subtype indication may be an access definition,
2183 -- if the array or container has elements of an anonymous access type.
2185 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id;
2186 -- For containers with Iterator and related aspects, the cursor is
2187 -- obtained by locating an entity with the proper name in the scope
2188 -- of the type.
2190 -----------------------------
2191 -- Check_Reverse_Iteration --
2192 -----------------------------
2194 procedure Check_Reverse_Iteration (Typ : Entity_Id) is
2195 begin
2196 if Reverse_Present (N) then
2197 if Is_Array_Type (Typ)
2198 or else Is_Reversible_Iterator (Typ)
2199 or else
2200 (Has_Aspect (Typ, Aspect_Iterable)
2201 and then
2202 Present
2203 (Get_Iterable_Type_Primitive (Typ, Name_Previous)))
2204 then
2205 null;
2206 else
2207 Error_Msg_N
2208 ("container type does not support reverse iteration", N);
2209 end if;
2210 end if;
2211 end Check_Reverse_Iteration;
2213 -------------------------------
2214 -- Check_Subtype_Definition --
2215 -------------------------------
2217 procedure Check_Subtype_Definition (Comp_Type : Entity_Id) is
2218 begin
2219 if No (Subt) then
2220 return;
2221 end if;
2223 if Is_Anonymous_Access_Type (Entity (Subt)) then
2224 if not Is_Anonymous_Access_Type (Comp_Type) then
2225 Error_Msg_NE
2226 ("component type& is not an anonymous access",
2227 Subt, Comp_Type);
2229 elsif not Conforming_Types
2230 (Designated_Type (Entity (Subt)),
2231 Designated_Type (Comp_Type),
2232 Fully_Conformant)
2233 then
2234 Error_Msg_NE
2235 ("subtype indication does not match component type&",
2236 Subt, Comp_Type);
2237 end if;
2239 elsif not Covers (Base_Type (Bas), Comp_Type)
2240 or else not Subtypes_Statically_Match (Bas, Comp_Type)
2241 then
2242 if Is_Array_Type (Typ) then
2243 Error_Msg_NE
2244 ("subtype indication does not match component type&",
2245 Subt, Comp_Type);
2246 else
2247 Error_Msg_NE
2248 ("subtype indication does not match element type&",
2249 Subt, Comp_Type);
2250 end if;
2251 end if;
2252 end Check_Subtype_Definition;
2254 ---------------------
2255 -- Get_Cursor_Type --
2256 ---------------------
2258 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id is
2259 Ent : Entity_Id;
2261 begin
2262 -- If iterator type is derived, the cursor is declared in the scope
2263 -- of the parent type.
2265 if Is_Derived_Type (Typ) then
2266 Ent := First_Entity (Scope (Etype (Typ)));
2267 else
2268 Ent := First_Entity (Scope (Typ));
2269 end if;
2271 while Present (Ent) loop
2272 exit when Chars (Ent) = Name_Cursor;
2273 Next_Entity (Ent);
2274 end loop;
2276 if No (Ent) then
2277 return Any_Type;
2278 end if;
2280 -- The cursor is the target of generated assignments in the
2281 -- loop, and cannot have a limited type.
2283 if Is_Limited_Type (Etype (Ent)) then
2284 Error_Msg_N ("cursor type cannot be limited", N);
2285 end if;
2287 return Etype (Ent);
2288 end Get_Cursor_Type;
2290 -- Start of processing for Analyze_Iterator_Specification
2292 begin
2293 Enter_Name (Def_Id);
2295 -- AI12-0151 specifies that when the subtype indication is present, it
2296 -- must statically match the type of the array or container element.
2297 -- To simplify this check, we introduce a subtype declaration with the
2298 -- given subtype indication when it carries a constraint, and rewrite
2299 -- the original as a reference to the created subtype entity.
2301 if Present (Subt) then
2302 if Nkind (Subt) = N_Subtype_Indication then
2303 declare
2304 S : constant Entity_Id := Make_Temporary (Sloc (Subt), 'S');
2305 Decl : constant Node_Id :=
2306 Make_Subtype_Declaration (Loc,
2307 Defining_Identifier => S,
2308 Subtype_Indication => New_Copy_Tree (Subt));
2309 begin
2310 Insert_Action (N, Decl);
2311 Analyze (Decl);
2312 Rewrite (Subt, New_Occurrence_Of (S, Sloc (Subt)));
2313 end;
2315 -- Ada 2022: the subtype definition may be for an anonymous
2316 -- access type.
2318 elsif Nkind (Subt) = N_Access_Definition then
2319 declare
2320 S : constant Entity_Id := Make_Temporary (Sloc (Subt), 'S');
2321 Decl : Node_Id;
2322 begin
2323 if Present (Subtype_Mark (Subt)) then
2324 Decl :=
2325 Make_Full_Type_Declaration (Loc,
2326 Defining_Identifier => S,
2327 Type_Definition =>
2328 Make_Access_To_Object_Definition (Loc,
2329 All_Present => True,
2330 Subtype_Indication =>
2331 New_Copy_Tree (Subtype_Mark (Subt))));
2333 else
2334 Decl :=
2335 Make_Full_Type_Declaration (Loc,
2336 Defining_Identifier => S,
2337 Type_Definition =>
2338 New_Copy_Tree
2339 (Access_To_Subprogram_Definition (Subt)));
2340 end if;
2342 Insert_Before (Parent (Parent (N)), Decl);
2343 Analyze (Decl);
2344 Freeze_Before (First (Statements (Parent (Parent (N)))), S);
2345 Rewrite (Subt, New_Occurrence_Of (S, Sloc (Subt)));
2346 end;
2347 else
2348 Analyze (Subt);
2349 end if;
2351 -- Save entity of subtype indication for subsequent check
2353 Bas := Entity (Subt);
2354 end if;
2356 Preanalyze_Range (Iter_Name);
2358 -- If the domain of iteration is a function call, make sure the function
2359 -- itself is frozen. This is an issue if this is a local expression
2360 -- function.
2362 if Nkind (Iter_Name) = N_Function_Call
2363 and then Is_Entity_Name (Name (Iter_Name))
2364 and then Full_Analysis
2365 and then (In_Assertion_Expr = 0 or else Assertions_Enabled)
2366 then
2367 Freeze_Before (N, Entity (Name (Iter_Name)));
2368 end if;
2370 -- Set the kind of the loop variable, which is not visible within the
2371 -- iterator name.
2373 Mutate_Ekind (Def_Id, E_Variable);
2375 -- Provide a link between the iterator variable and the container, for
2376 -- subsequent use in cross-reference and modification information.
2378 if Of_Present (N) then
2379 Set_Related_Expression (Def_Id, Iter_Name);
2381 -- For a container, the iterator is specified through the aspect
2383 if not Is_Array_Type (Etype (Iter_Name)) then
2384 declare
2385 Iterator : constant Entity_Id :=
2386 Find_Value_Of_Aspect
2387 (Etype (Iter_Name), Aspect_Default_Iterator);
2389 I : Interp_Index;
2390 It : Interp;
2392 begin
2393 -- The domain of iteration must implement either the RM
2394 -- iterator interface, or the SPARK Iterable aspect.
2396 if No (Iterator) then
2397 if No (Find_Aspect (Etype (Iter_Name), Aspect_Iterable)) then
2398 Error_Msg_NE
2399 ("cannot iterate over&",
2400 N, Base_Type (Etype (Iter_Name)));
2401 return;
2402 end if;
2404 elsif not Is_Overloaded (Iterator) then
2405 Check_Reverse_Iteration (Etype (Iterator));
2407 -- If Iterator is overloaded, use reversible iterator if one is
2408 -- available.
2410 elsif Is_Overloaded (Iterator) then
2411 Get_First_Interp (Iterator, I, It);
2412 while Present (It.Nam) loop
2413 if Ekind (It.Nam) = E_Function
2414 and then Is_Reversible_Iterator (Etype (It.Nam))
2415 then
2416 Set_Etype (Iterator, It.Typ);
2417 Set_Entity (Iterator, It.Nam);
2418 exit;
2419 end if;
2421 Get_Next_Interp (I, It);
2422 end loop;
2424 Check_Reverse_Iteration (Etype (Iterator));
2425 end if;
2426 end;
2427 end if;
2428 end if;
2430 -- If the domain of iteration is an expression, create a declaration for
2431 -- it, so that finalization actions are introduced outside of the loop.
2432 -- The declaration must be a renaming (both in GNAT and GNATprove
2433 -- modes), because the body of the loop may assign to elements.
2435 if not Is_Entity_Name (Iter_Name)
2437 -- Do not perform this expansion in preanalysis
2439 and then Full_Analysis
2441 -- Do not perform this expansion when expansion is disabled, where the
2442 -- temporary may hide the transformation of a selected component into
2443 -- a prefixed function call, and references need to see the original
2444 -- expression.
2446 and then (Expander_Active or GNATprove_Mode)
2447 then
2448 declare
2449 Id : constant Entity_Id := Make_Temporary (Loc, 'R', Iter_Name);
2450 Decl : Node_Id;
2451 Act_S : Node_Id;
2453 begin
2455 -- If the domain of iteration is an array component that depends
2456 -- on a discriminant, create actual subtype for it. Preanalysis
2457 -- does not generate the actual subtype of a selected component.
2459 if Nkind (Iter_Name) = N_Selected_Component
2460 and then Is_Array_Type (Etype (Iter_Name))
2461 then
2462 Act_S :=
2463 Build_Actual_Subtype_Of_Component
2464 (Etype (Selector_Name (Iter_Name)), Iter_Name);
2465 Insert_Action (N, Act_S);
2467 if Present (Act_S) then
2468 Typ := Defining_Identifier (Act_S);
2469 else
2470 Typ := Etype (Iter_Name);
2471 end if;
2473 else
2474 Typ := Etype (Iter_Name);
2476 -- Verify that the expression produces an iterator
2478 if not Of_Present (N) and then not Is_Iterator (Typ)
2479 and then not Is_Array_Type (Typ)
2480 and then No (Find_Aspect (Typ, Aspect_Iterable))
2481 then
2482 Error_Msg_N
2483 ("expect object that implements iterator interface",
2484 Iter_Name);
2485 end if;
2486 end if;
2488 -- Protect against malformed iterator
2490 if Typ = Any_Type then
2491 Error_Msg_N ("invalid expression in loop iterator", Iter_Name);
2492 return;
2493 end if;
2495 if not Of_Present (N) then
2496 Check_Reverse_Iteration (Typ);
2497 end if;
2499 -- For an element iteration over a slice, we must complete
2500 -- the resolution and expansion of the slice bounds. These
2501 -- can be arbitrary expressions, and the preanalysis that
2502 -- was performed in preparation for the iteration may have
2503 -- generated an itype whose bounds must be fully expanded.
2504 -- We set the parent node to provide a proper insertion
2505 -- point for generated actions, if any.
2507 if Nkind (Iter_Name) = N_Slice
2508 and then Nkind (Discrete_Range (Iter_Name)) = N_Range
2509 and then not Analyzed (Discrete_Range (Iter_Name))
2510 then
2511 declare
2512 Indx : constant Node_Id :=
2513 Entity (First_Index (Etype (Iter_Name)));
2514 begin
2515 Set_Parent (Indx, Iter_Name);
2516 Resolve (Scalar_Range (Indx), Etype (Indx));
2517 end;
2518 end if;
2520 -- The name in the renaming declaration may be a function call.
2521 -- Indicate that it does not come from source, to suppress
2522 -- spurious warnings on renamings of parameterless functions,
2523 -- a common enough idiom in user-defined iterators.
2525 Decl :=
2526 Make_Object_Renaming_Declaration (Loc,
2527 Defining_Identifier => Id,
2528 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
2529 Name =>
2530 New_Copy_Tree (Iter_Name, New_Sloc => Loc));
2531 Set_Comes_From_Iterator (Decl);
2533 Insert_Actions (Parent (Parent (N)), New_List (Decl));
2534 Rewrite (Name (N), New_Occurrence_Of (Id, Loc));
2535 Analyze (Name (N));
2536 Set_Etype (Id, Typ);
2537 Set_Etype (Name (N), Typ);
2538 end;
2540 -- Container is an entity or an array with uncontrolled components, or
2541 -- else it is a container iterator given by a function call, typically
2542 -- called Iterate in the case of predefined containers, even though
2543 -- Iterate is not a reserved name. What matters is that the return type
2544 -- of the function is an iterator type.
2546 elsif Is_Entity_Name (Iter_Name) then
2547 Analyze (Iter_Name);
2549 if Nkind (Iter_Name) = N_Function_Call then
2550 declare
2551 C : constant Node_Id := Name (Iter_Name);
2552 I : Interp_Index;
2553 It : Interp;
2555 begin
2556 if not Is_Overloaded (Iter_Name) then
2557 Resolve (Iter_Name, Etype (C));
2559 else
2560 Get_First_Interp (C, I, It);
2561 while It.Typ /= Empty loop
2562 if Reverse_Present (N) then
2563 if Is_Reversible_Iterator (It.Typ) then
2564 Resolve (Iter_Name, It.Typ);
2565 exit;
2566 end if;
2568 elsif Is_Iterator (It.Typ) then
2569 Resolve (Iter_Name, It.Typ);
2570 exit;
2571 end if;
2573 Get_Next_Interp (I, It);
2574 end loop;
2575 end if;
2576 end;
2578 -- Domain of iteration is not overloaded
2580 else
2581 Resolve (Iter_Name);
2582 end if;
2584 if not Of_Present (N) then
2585 Check_Reverse_Iteration (Etype (Iter_Name));
2586 end if;
2587 end if;
2589 -- Get base type of container, for proper retrieval of Cursor type
2590 -- and primitive operations.
2592 Typ := Base_Type (Etype (Iter_Name));
2594 if Is_Array_Type (Typ) then
2595 if Of_Present (N) then
2596 Set_Etype (Def_Id, Component_Type (Typ));
2598 -- The loop variable is aliased if the array components are
2599 -- aliased. Likewise for the independent aspect.
2601 Set_Is_Aliased (Def_Id, Has_Aliased_Components (Typ));
2602 Set_Is_Independent (Def_Id, Has_Independent_Components (Typ));
2604 -- AI12-0047 stipulates that the domain (array or container)
2605 -- cannot be a component that depends on a discriminant if the
2606 -- enclosing object is mutable, to prevent a modification of the
2607 -- domain of iteration in the course of an iteration.
2609 -- If the object is an expression it has been captured in a
2610 -- temporary, so examine original node.
2612 if Nkind (Original_Node (Iter_Name)) = N_Selected_Component
2613 and then Is_Dependent_Component_Of_Mutable_Object
2614 (Original_Node (Iter_Name))
2615 then
2616 Error_Msg_N
2617 ("iterable name cannot be a discriminant-dependent "
2618 & "component of a mutable object", N);
2619 end if;
2621 Check_Subtype_Definition (Component_Type (Typ));
2623 -- Here we have a missing Range attribute
2625 else
2626 Error_Msg_N
2627 ("missing Range attribute in iteration over an array", N);
2629 -- In Ada 2012 mode, this may be an attempt at an iterator
2631 if Ada_Version >= Ada_2012 then
2632 Error_Msg_NE
2633 ("\if& is meant to designate an element of the array, use OF",
2634 N, Def_Id);
2635 end if;
2637 -- Prevent cascaded errors
2639 Mutate_Ekind (Def_Id, E_Loop_Parameter);
2640 Set_Etype (Def_Id, Etype (First_Index (Typ)));
2641 end if;
2643 -- Check for type error in iterator
2645 elsif Typ = Any_Type then
2646 return;
2648 -- Iteration over a container
2650 else
2651 Mutate_Ekind (Def_Id, E_Loop_Parameter);
2652 Error_Msg_Ada_2012_Feature ("container iterator", Sloc (N));
2654 -- OF present
2656 if Of_Present (N) then
2657 if Has_Aspect (Typ, Aspect_Iterable) then
2658 declare
2659 Elt : constant Entity_Id :=
2660 Get_Iterable_Type_Primitive (Typ, Name_Element);
2661 begin
2662 if No (Elt) then
2663 Error_Msg_N
2664 ("missing Element primitive for iteration", N);
2665 else
2666 Set_Etype (Def_Id, Etype (Elt));
2667 Check_Reverse_Iteration (Typ);
2668 end if;
2669 end;
2671 Check_Subtype_Definition (Etype (Def_Id));
2673 -- For a predefined container, the type of the loop variable is
2674 -- the Iterator_Element aspect of the container type.
2676 else
2677 declare
2678 Element : constant Entity_Id :=
2679 Find_Value_Of_Aspect
2680 (Typ, Aspect_Iterator_Element);
2681 Iterator : constant Entity_Id :=
2682 Find_Value_Of_Aspect
2683 (Typ, Aspect_Default_Iterator);
2684 Orig_Iter_Name : constant Node_Id :=
2685 Original_Node (Iter_Name);
2686 Cursor_Type : Entity_Id;
2688 begin
2689 if No (Element) then
2690 Error_Msg_NE ("cannot iterate over&", N, Typ);
2691 return;
2693 else
2694 Set_Etype (Def_Id, Entity (Element));
2695 Cursor_Type := Get_Cursor_Type (Typ);
2696 pragma Assert (Present (Cursor_Type));
2698 Check_Subtype_Definition (Etype (Def_Id));
2700 -- If the container has a variable indexing aspect, the
2701 -- element is a variable and is modifiable in the loop.
2703 if Has_Aspect (Typ, Aspect_Variable_Indexing) then
2704 Mutate_Ekind (Def_Id, E_Variable);
2705 end if;
2707 -- If the container is a constant, iterating over it
2708 -- requires a Constant_Indexing operation.
2710 if not Is_Variable (Iter_Name)
2711 and then not Has_Aspect (Typ, Aspect_Constant_Indexing)
2712 then
2713 Error_Msg_N
2714 ("iteration over constant container require "
2715 & "constant_indexing aspect", N);
2717 -- The Iterate function may have an in_out parameter,
2718 -- and a constant container is thus illegal.
2720 elsif Present (Iterator)
2721 and then Ekind (Entity (Iterator)) = E_Function
2722 and then Ekind (First_Formal (Entity (Iterator))) /=
2723 E_In_Parameter
2724 and then not Is_Variable (Iter_Name)
2725 then
2726 Error_Msg_N ("variable container expected", N);
2727 end if;
2729 -- Detect a case where the iterator denotes a component
2730 -- of a mutable object which depends on a discriminant.
2731 -- Note that the iterator may denote a function call in
2732 -- qualified form, in which case this check should not
2733 -- be performed.
2735 if Nkind (Orig_Iter_Name) = N_Selected_Component
2736 and then
2737 Present (Entity (Selector_Name (Orig_Iter_Name)))
2738 and then
2739 Ekind (Entity (Selector_Name (Orig_Iter_Name))) in
2740 E_Component | E_Discriminant
2741 and then Is_Dependent_Component_Of_Mutable_Object
2742 (Orig_Iter_Name)
2743 then
2744 Error_Msg_N
2745 ("container cannot be a discriminant-dependent "
2746 & "component of a mutable object", N);
2747 end if;
2748 end if;
2749 end;
2750 end if;
2752 -- IN iterator, domain is a range, a call to Iterate function,
2753 -- or an object/actual parameter of an iterator type.
2755 else
2756 -- If the type of the name is class-wide and its root type is a
2757 -- derived type, the primitive operations (First, Next, etc.) are
2758 -- those inherited by its specific type. Calls to these primitives
2759 -- will be dispatching.
2761 if Is_Class_Wide_Type (Typ)
2762 and then Is_Derived_Type (Etype (Typ))
2763 then
2764 Typ := Etype (Typ);
2765 end if;
2767 -- For an iteration of the form IN, the name must denote an
2768 -- iterator, typically the result of a call to Iterate. Give a
2769 -- useful error message when the name is a container by itself.
2771 -- The type may be a formal container type, which has to have
2772 -- an Iterable aspect detailing the required primitives.
2774 if Is_Entity_Name (Original_Node (Name (N)))
2775 and then not Is_Iterator (Typ)
2776 then
2777 if Has_Aspect (Typ, Aspect_Iterable) then
2778 null;
2780 elsif not Has_Aspect (Typ, Aspect_Iterator_Element) then
2781 Error_Msg_NE
2782 ("cannot iterate over&", Name (N), Typ);
2783 else
2784 Error_Msg_N
2785 ("name must be an iterator, not a container", Name (N));
2786 end if;
2788 if Has_Aspect (Typ, Aspect_Iterable) then
2789 null;
2790 else
2791 Error_Msg_NE
2792 ("\to iterate directly over the elements of a container, "
2793 & "write `of &`", Name (N), Original_Node (Name (N)));
2795 -- No point in continuing analysis of iterator spec
2797 return;
2798 end if;
2799 end if;
2801 -- If the name is a call (typically prefixed) to some Iterate
2802 -- function, it has been rewritten as an object declaration.
2803 -- If that object is a selected component, verify that it is not
2804 -- a component of an unconstrained mutable object.
2806 if Nkind (Iter_Name) = N_Identifier
2807 or else (not Expander_Active and Comes_From_Source (Iter_Name))
2808 then
2809 declare
2810 Orig_Node : constant Node_Id := Original_Node (Iter_Name);
2811 Iter_Kind : constant Node_Kind := Nkind (Orig_Node);
2812 Obj : Node_Id;
2814 begin
2815 if Iter_Kind = N_Selected_Component then
2816 Obj := Prefix (Orig_Node);
2818 elsif Iter_Kind = N_Function_Call then
2819 Obj := First_Actual (Orig_Node);
2821 -- If neither, the name comes from source
2823 else
2824 Obj := Iter_Name;
2825 end if;
2827 if Nkind (Obj) = N_Selected_Component
2828 and then Is_Dependent_Component_Of_Mutable_Object (Obj)
2829 then
2830 Error_Msg_N
2831 ("container cannot be a discriminant-dependent "
2832 & "component of a mutable object", N);
2833 end if;
2834 end;
2835 end if;
2837 -- The result type of Iterate function is the classwide type of
2838 -- the interface parent. We need the specific Cursor type defined
2839 -- in the container package. We obtain it by name for a predefined
2840 -- container, or through the Iterable aspect for a formal one.
2842 if Has_Aspect (Typ, Aspect_Iterable) then
2843 Set_Etype (Def_Id,
2844 Get_Cursor_Type
2845 (Parent (Find_Value_Of_Aspect (Typ, Aspect_Iterable)),
2846 Typ));
2848 else
2849 Set_Etype (Def_Id, Get_Cursor_Type (Typ));
2850 Check_Reverse_Iteration (Etype (Iter_Name));
2851 end if;
2853 end if;
2854 end if;
2856 if Present (Iterator_Filter (N)) then
2857 -- Preanalyze the filter. Expansion will take place when enclosing
2858 -- loop is expanded.
2860 Preanalyze_And_Resolve (Iterator_Filter (N), Standard_Boolean);
2861 end if;
2862 end Analyze_Iterator_Specification;
2864 -------------------
2865 -- Analyze_Label --
2866 -------------------
2868 -- Note: the semantic work required for analyzing labels (setting them as
2869 -- reachable) was done in a prepass through the statements in the block,
2870 -- so that forward gotos would be properly handled. See Analyze_Statements
2871 -- for further details. The only processing required here is to deal with
2872 -- optimizations that depend on an assumption of sequential control flow,
2873 -- since of course the occurrence of a label breaks this assumption.
2875 procedure Analyze_Label (N : Node_Id) is
2876 pragma Warnings (Off, N);
2877 begin
2878 Kill_Current_Values;
2879 end Analyze_Label;
2881 ------------------------------------------
2882 -- Analyze_Loop_Parameter_Specification --
2883 ------------------------------------------
2885 procedure Analyze_Loop_Parameter_Specification (N : Node_Id) is
2886 Loop_Nod : constant Node_Id := Parent (Parent (N));
2888 procedure Check_Controlled_Array_Attribute (DS : Node_Id);
2889 -- If the bounds are given by a 'Range reference on a function call
2890 -- that returns a controlled array, introduce an explicit declaration
2891 -- to capture the bounds, so that the function result can be finalized
2892 -- in timely fashion.
2894 procedure Check_Predicate_Use (T : Entity_Id);
2895 -- Diagnose Attempt to iterate through non-static predicate. Note that
2896 -- a type with inherited predicates may have both static and dynamic
2897 -- forms. In this case it is not sufficient to check the static
2898 -- predicate function only, look for a dynamic predicate aspect as well.
2900 procedure Process_Bounds (R : Node_Id);
2901 -- If the iteration is given by a range, create temporaries and
2902 -- assignment statements block to capture the bounds and perform
2903 -- required finalization actions in case a bound includes a function
2904 -- call that uses the temporary stack. We first preanalyze a copy of
2905 -- the range in order to determine the expected type, and analyze and
2906 -- resolve the original bounds.
2908 --------------------------------------
2909 -- Check_Controlled_Array_Attribute --
2910 --------------------------------------
2912 procedure Check_Controlled_Array_Attribute (DS : Node_Id) is
2913 begin
2914 if Nkind (DS) = N_Attribute_Reference
2915 and then Is_Entity_Name (Prefix (DS))
2916 and then Ekind (Entity (Prefix (DS))) = E_Function
2917 and then Is_Array_Type (Etype (Entity (Prefix (DS))))
2918 and then
2919 Is_Controlled (Component_Type (Etype (Entity (Prefix (DS)))))
2920 and then Expander_Active
2921 then
2922 declare
2923 Loc : constant Source_Ptr := Sloc (N);
2924 Arr : constant Entity_Id := Etype (Entity (Prefix (DS)));
2925 Indx : constant Entity_Id :=
2926 Base_Type (Etype (First_Index (Arr)));
2927 Subt : constant Entity_Id := Make_Temporary (Loc, 'S');
2928 Decl : Node_Id;
2930 begin
2931 Decl :=
2932 Make_Subtype_Declaration (Loc,
2933 Defining_Identifier => Subt,
2934 Subtype_Indication =>
2935 Make_Subtype_Indication (Loc,
2936 Subtype_Mark => New_Occurrence_Of (Indx, Loc),
2937 Constraint =>
2938 Make_Range_Constraint (Loc, Relocate_Node (DS))));
2939 Insert_Before (Loop_Nod, Decl);
2940 Analyze (Decl);
2942 Rewrite (DS,
2943 Make_Attribute_Reference (Loc,
2944 Prefix => New_Occurrence_Of (Subt, Loc),
2945 Attribute_Name => Attribute_Name (DS)));
2947 Analyze (DS);
2948 end;
2949 end if;
2950 end Check_Controlled_Array_Attribute;
2952 -------------------------
2953 -- Check_Predicate_Use --
2954 -------------------------
2956 procedure Check_Predicate_Use (T : Entity_Id) is
2957 begin
2958 -- A predicated subtype is illegal in loops and related constructs
2959 -- if the predicate is not static, or if it is a non-static subtype
2960 -- of a statically predicated subtype.
2962 if Is_Discrete_Type (T)
2963 and then Has_Predicates (T)
2964 and then (not Has_Static_Predicate (T)
2965 or else not Is_Static_Subtype (T)
2966 or else Has_Dynamic_Predicate_Aspect (T))
2967 then
2968 -- Seems a confusing message for the case of a static predicate
2969 -- with a non-static subtype???
2971 Bad_Predicated_Subtype_Use
2972 ("cannot use subtype& with non-static predicate for loop "
2973 & "iteration", Discrete_Subtype_Definition (N),
2974 T, Suggest_Static => True);
2976 elsif Inside_A_Generic
2977 and then Is_Generic_Formal (T)
2978 and then Is_Discrete_Type (T)
2979 then
2980 Set_No_Dynamic_Predicate_On_Actual (T);
2981 end if;
2982 end Check_Predicate_Use;
2984 --------------------
2985 -- Process_Bounds --
2986 --------------------
2988 procedure Process_Bounds (R : Node_Id) is
2989 Loc : constant Source_Ptr := Sloc (N);
2991 function One_Bound
2992 (Original_Bound : Node_Id;
2993 Analyzed_Bound : Node_Id;
2994 Typ : Entity_Id) return Node_Id;
2995 -- Capture value of bound and return captured value
2997 ---------------
2998 -- One_Bound --
2999 ---------------
3001 function One_Bound
3002 (Original_Bound : Node_Id;
3003 Analyzed_Bound : Node_Id;
3004 Typ : Entity_Id) return Node_Id
3006 Assign : Node_Id;
3007 Decl : Node_Id;
3008 Id : Entity_Id;
3010 begin
3011 -- If the bound is a constant or an object, no need for a separate
3012 -- declaration. If the bound is the result of previous expansion
3013 -- it is already analyzed and should not be modified. Note that
3014 -- the Bound will be resolved later, if needed, as part of the
3015 -- call to Make_Index (literal bounds may need to be resolved to
3016 -- type Integer).
3018 if Analyzed (Original_Bound) then
3019 return Original_Bound;
3021 elsif Nkind (Analyzed_Bound) in
3022 N_Integer_Literal | N_Character_Literal
3023 or else Is_Entity_Name (Analyzed_Bound)
3024 then
3025 Analyze_And_Resolve (Original_Bound, Typ);
3026 return Original_Bound;
3028 elsif Inside_Class_Condition_Preanalysis then
3029 Analyze_And_Resolve (Original_Bound, Typ);
3030 return Original_Bound;
3031 end if;
3033 -- Normally, the best approach is simply to generate a constant
3034 -- declaration that captures the bound. However, there is a nasty
3035 -- case where this is wrong. If the bound is complex, and has a
3036 -- possible use of the secondary stack, we need to generate a
3037 -- separate assignment statement to ensure the creation of a block
3038 -- which will release the secondary stack.
3040 -- We prefer the constant declaration, since it leaves us with a
3041 -- proper trace of the value, useful in optimizations that get rid
3042 -- of junk range checks.
3044 if not Has_Sec_Stack_Call (Analyzed_Bound) then
3045 Analyze_And_Resolve (Original_Bound, Typ);
3047 -- Ensure that the bound is valid. This check should not be
3048 -- generated when the range belongs to a quantified expression
3049 -- as the construct is still not expanded into its final form.
3051 if Nkind (Parent (R)) /= N_Loop_Parameter_Specification
3052 or else Nkind (Parent (Parent (R))) /= N_Quantified_Expression
3053 then
3054 Ensure_Valid (Original_Bound);
3055 end if;
3057 Force_Evaluation (Original_Bound);
3058 return Original_Bound;
3059 end if;
3061 Id := Make_Temporary (Loc, 'R', Original_Bound);
3063 -- Here we make a declaration with a separate assignment
3064 -- statement, and insert before loop header.
3066 Decl :=
3067 Make_Object_Declaration (Loc,
3068 Defining_Identifier => Id,
3069 Object_Definition => New_Occurrence_Of (Typ, Loc));
3071 Assign :=
3072 Make_Assignment_Statement (Loc,
3073 Name => New_Occurrence_Of (Id, Loc),
3074 Expression => Relocate_Node (Original_Bound));
3076 Insert_Actions (Loop_Nod, New_List (Decl, Assign));
3078 -- Now that this temporary variable is initialized we decorate it
3079 -- as safe-to-reevaluate to inform to the backend that no further
3080 -- asignment will be issued and hence it can be handled as side
3081 -- effect free. Note that this decoration must be done when the
3082 -- assignment has been analyzed because otherwise it will be
3083 -- rejected (see Analyze_Assignment).
3085 Set_Is_Safe_To_Reevaluate (Id);
3087 Rewrite (Original_Bound, New_Occurrence_Of (Id, Loc));
3089 if Nkind (Assign) = N_Assignment_Statement then
3090 return Expression (Assign);
3091 else
3092 return Original_Bound;
3093 end if;
3094 end One_Bound;
3096 Hi : constant Node_Id := High_Bound (R);
3097 Lo : constant Node_Id := Low_Bound (R);
3098 R_Copy : constant Node_Id := New_Copy_Tree (R);
3099 New_Hi : Node_Id;
3100 New_Lo : Node_Id;
3101 Typ : Entity_Id;
3103 -- Start of processing for Process_Bounds
3105 begin
3106 Set_Parent (R_Copy, Parent (R));
3107 Preanalyze_Range (R_Copy);
3108 Typ := Etype (R_Copy);
3110 -- If the type of the discrete range is Universal_Integer, then the
3111 -- bound's type must be resolved to Integer, and any object used to
3112 -- hold the bound must also have type Integer, unless the literal
3113 -- bounds are constant-folded expressions with a user-defined type.
3115 if Typ = Universal_Integer then
3116 if Nkind (Lo) = N_Integer_Literal
3117 and then Present (Etype (Lo))
3118 and then Scope (Etype (Lo)) /= Standard_Standard
3119 then
3120 Typ := Etype (Lo);
3122 elsif Nkind (Hi) = N_Integer_Literal
3123 and then Present (Etype (Hi))
3124 and then Scope (Etype (Hi)) /= Standard_Standard
3125 then
3126 Typ := Etype (Hi);
3128 else
3129 Typ := Standard_Integer;
3130 end if;
3131 end if;
3133 Set_Etype (R, Typ);
3135 New_Lo := One_Bound (Lo, Low_Bound (R_Copy), Typ);
3136 New_Hi := One_Bound (Hi, High_Bound (R_Copy), Typ);
3138 -- Propagate staticness to loop range itself, in case the
3139 -- corresponding subtype is static.
3141 if New_Lo /= Lo and then Is_OK_Static_Expression (New_Lo) then
3142 Rewrite (Low_Bound (R), New_Copy (New_Lo));
3143 end if;
3145 if New_Hi /= Hi and then Is_OK_Static_Expression (New_Hi) then
3146 Rewrite (High_Bound (R), New_Copy (New_Hi));
3147 end if;
3148 end Process_Bounds;
3150 -- Local variables
3152 DS : constant Node_Id := Discrete_Subtype_Definition (N);
3153 Id : constant Entity_Id := Defining_Identifier (N);
3155 DS_Copy : Node_Id;
3157 -- Start of processing for Analyze_Loop_Parameter_Specification
3159 begin
3160 Enter_Name (Id);
3162 -- We always consider the loop variable to be referenced, since the loop
3163 -- may be used just for counting purposes.
3165 Generate_Reference (Id, N, ' ');
3167 -- Check for the case of loop variable hiding a local variable (used
3168 -- later on to give a nice warning if the hidden variable is never
3169 -- assigned).
3171 declare
3172 H : constant Entity_Id := Homonym (Id);
3173 begin
3174 if Present (H)
3175 and then Ekind (H) = E_Variable
3176 and then Is_Discrete_Type (Etype (H))
3177 and then Enclosing_Dynamic_Scope (H) = Enclosing_Dynamic_Scope (Id)
3178 then
3179 Set_Hiding_Loop_Variable (H, Id);
3180 end if;
3181 end;
3183 -- Analyze the subtype definition and create temporaries for the bounds.
3184 -- Do not evaluate the range when preanalyzing a quantified expression
3185 -- because bounds expressed as function calls with side effects will be
3186 -- incorrectly replicated.
3188 if Nkind (DS) = N_Range
3189 and then Expander_Active
3190 and then Nkind (Parent (N)) /= N_Quantified_Expression
3191 then
3192 Process_Bounds (DS);
3194 -- Either the expander not active or the range of iteration is a subtype
3195 -- indication, an entity, or a function call that yields an aggregate or
3196 -- a container.
3198 else
3199 DS_Copy := New_Copy_Tree (DS);
3200 Set_Parent (DS_Copy, Parent (DS));
3201 Preanalyze_Range (DS_Copy);
3203 -- Ada 2012: If the domain of iteration is:
3205 -- a) a function call,
3206 -- b) an identifier that is not a type,
3207 -- c) an attribute reference 'Old (within a postcondition),
3208 -- d) an unchecked conversion or a qualified expression with
3209 -- the proper iterator type.
3211 -- then it is an iteration over a container. It was classified as
3212 -- a loop specification by the parser, and must be rewritten now
3213 -- to activate container iteration. The last case will occur within
3214 -- an expanded inlined call, where the expansion wraps an actual in
3215 -- an unchecked conversion when needed. The expression of the
3216 -- conversion is always an object.
3218 if Nkind (DS_Copy) = N_Function_Call
3220 or else (Is_Entity_Name (DS_Copy)
3221 and then not Is_Type (Entity (DS_Copy)))
3223 or else (Nkind (DS_Copy) = N_Attribute_Reference
3224 and then Attribute_Name (DS_Copy) in
3225 Name_Loop_Entry | Name_Old)
3227 or else Has_Aspect (Etype (DS_Copy), Aspect_Iterable)
3229 or else Nkind (DS_Copy) = N_Unchecked_Type_Conversion
3230 or else (Nkind (DS_Copy) = N_Qualified_Expression
3231 and then Is_Iterator (Etype (DS_Copy)))
3232 then
3233 -- This is an iterator specification. Rewrite it as such and
3234 -- analyze it to capture function calls that may require
3235 -- finalization actions.
3237 declare
3238 I_Spec : constant Node_Id :=
3239 Make_Iterator_Specification (Sloc (N),
3240 Defining_Identifier => Relocate_Node (Id),
3241 Name => DS_Copy,
3242 Subtype_Indication => Empty,
3243 Reverse_Present => Reverse_Present (N));
3244 Scheme : constant Node_Id := Parent (N);
3246 begin
3247 Set_Iterator_Specification (Scheme, I_Spec);
3248 Set_Loop_Parameter_Specification (Scheme, Empty);
3249 Set_Iterator_Filter (I_Spec,
3250 Relocate_Node (Iterator_Filter (N)));
3252 Analyze_Iterator_Specification (I_Spec);
3254 -- In a generic context, analyze the original domain of
3255 -- iteration, for name capture.
3257 if not Expander_Active then
3258 Analyze (DS);
3259 end if;
3261 -- Set kind of loop parameter, which may be used in the
3262 -- subsequent analysis of the condition in a quantified
3263 -- expression.
3265 Mutate_Ekind (Id, E_Loop_Parameter);
3266 return;
3267 end;
3269 -- Domain of iteration is not a function call, and is side-effect
3270 -- free.
3272 else
3273 -- A quantified expression that appears in a pre/post condition
3274 -- is preanalyzed several times. If the range is given by an
3275 -- attribute reference it is rewritten as a range, and this is
3276 -- done even with expansion disabled. If the type is already set
3277 -- do not reanalyze, because a range with static bounds may be
3278 -- typed Integer by default.
3280 if Nkind (Parent (N)) = N_Quantified_Expression
3281 and then Present (Etype (DS))
3282 then
3283 null;
3284 else
3285 Analyze (DS);
3286 end if;
3287 end if;
3288 end if;
3290 if DS = Error then
3291 return;
3292 end if;
3294 -- Some additional checks if we are iterating through a type
3296 if Is_Entity_Name (DS)
3297 and then Present (Entity (DS))
3298 and then Is_Type (Entity (DS))
3299 then
3300 -- The subtype indication may denote the completion of an incomplete
3301 -- type declaration.
3303 if Ekind (Entity (DS)) = E_Incomplete_Type then
3304 Set_Entity (DS, Get_Full_View (Entity (DS)));
3305 Set_Etype (DS, Entity (DS));
3306 end if;
3308 Check_Predicate_Use (Entity (DS));
3309 end if;
3311 -- Error if not discrete type
3313 if not Is_Discrete_Type (Etype (DS)) then
3314 Wrong_Type (DS, Any_Discrete);
3315 Set_Etype (DS, Any_Type);
3316 end if;
3318 Check_Controlled_Array_Attribute (DS);
3320 if Nkind (DS) = N_Subtype_Indication then
3321 Check_Predicate_Use (Entity (Subtype_Mark (DS)));
3322 end if;
3324 if Nkind (DS) not in N_Raise_xxx_Error then
3325 Make_Index (DS, N);
3326 end if;
3328 Mutate_Ekind (Id, E_Loop_Parameter);
3330 -- A quantified expression which appears in a pre- or post-condition may
3331 -- be analyzed multiple times. The analysis of the range creates several
3332 -- itypes which reside in different scopes depending on whether the pre-
3333 -- or post-condition has been expanded. Update the type of the loop
3334 -- variable to reflect the proper itype at each stage of analysis.
3336 -- Loop_Nod might not be present when we are preanalyzing a class-wide
3337 -- pre/postcondition since preanalysis occurs in a place unrelated to
3338 -- the actual code and the quantified expression may be the outermost
3339 -- expression of the class-wide condition.
3341 if No (Etype (Id))
3342 or else Etype (Id) = Any_Type
3343 or else
3344 (Present (Etype (Id))
3345 and then Is_Itype (Etype (Id))
3346 and then Present (Loop_Nod)
3347 and then Nkind (Parent (Loop_Nod)) = N_Expression_With_Actions
3348 and then Nkind (Original_Node (Parent (Loop_Nod))) =
3349 N_Quantified_Expression)
3350 then
3351 Set_Etype (Id, Etype (DS));
3352 end if;
3354 -- Treat a range as an implicit reference to the type, to inhibit
3355 -- spurious warnings.
3357 Generate_Reference (Base_Type (Etype (DS)), N, ' ');
3358 Set_Is_Known_Valid (Id, True);
3360 -- The loop is not a declarative part, so the loop variable must be
3361 -- frozen explicitly. Do not freeze while preanalyzing a quantified
3362 -- expression because the freeze node will not be inserted into the
3363 -- tree due to flag Is_Spec_Expression being set.
3365 if Nkind (Parent (N)) /= N_Quantified_Expression then
3366 declare
3367 Flist : constant List_Id := Freeze_Entity (Id, N);
3368 begin
3369 Insert_Actions (N, Flist);
3370 end;
3371 end if;
3373 -- Case where we have a range or a subtype, get type bounds
3375 if Nkind (DS) in N_Range | N_Subtype_Indication
3376 and then not Error_Posted (DS)
3377 and then Etype (DS) /= Any_Type
3378 and then Is_Discrete_Type (Etype (DS))
3379 then
3380 declare
3381 L : Node_Id;
3382 H : Node_Id;
3383 Null_Range : Boolean := False;
3385 begin
3386 if Nkind (DS) = N_Range then
3387 L := Low_Bound (DS);
3388 H := High_Bound (DS);
3389 else
3390 L :=
3391 Type_Low_Bound (Underlying_Type (Etype (Subtype_Mark (DS))));
3392 H :=
3393 Type_High_Bound (Underlying_Type (Etype (Subtype_Mark (DS))));
3394 end if;
3396 -- Check for null or possibly null range and issue warning. We
3397 -- suppress such messages in generic templates and instances,
3398 -- because in practice they tend to be dubious in these cases. The
3399 -- check applies as well to rewritten array element loops where a
3400 -- null range may be detected statically.
3402 if Compile_Time_Compare (L, H, Assume_Valid => True) = GT then
3403 if Compile_Time_Compare (L, H, Assume_Valid => False) = GT then
3404 -- Since we know the range of the loop is always null,
3405 -- set the appropriate flag to remove the loop entirely
3406 -- during expansion.
3408 Set_Is_Null_Loop (Loop_Nod);
3409 Null_Range := True;
3410 end if;
3412 -- Suppress the warning if inside a generic template or
3413 -- instance, since in practice they tend to be dubious in these
3414 -- cases since they can result from intended parameterization.
3416 if not Inside_A_Generic and then not In_Instance then
3418 -- Specialize msg if invalid values could make the loop
3419 -- non-null after all.
3421 if Null_Range then
3422 if Comes_From_Source (N) then
3423 Error_Msg_N
3424 ("??loop range is null, loop will not execute", DS);
3425 end if;
3427 -- Here is where the loop could execute because of
3428 -- invalid values, so issue appropriate message.
3430 elsif Comes_From_Source (N) then
3431 Error_Msg_N
3432 ("??loop range may be null, loop may not execute",
3433 DS);
3434 Error_Msg_N
3435 ("??can only execute if invalid values are present",
3436 DS);
3437 end if;
3438 end if;
3440 -- In either case, suppress warnings in the body of the loop,
3441 -- since it is likely that these warnings will be inappropriate
3442 -- if the loop never actually executes, which is likely.
3444 Set_Suppress_Loop_Warnings (Loop_Nod);
3446 -- The other case for a warning is a reverse loop where the
3447 -- upper bound is the integer literal zero or one, and the
3448 -- lower bound may exceed this value.
3450 -- For example, we have
3452 -- for J in reverse N .. 1 loop
3454 -- In practice, this is very likely to be a case of reversing
3455 -- the bounds incorrectly in the range.
3457 elsif Reverse_Present (N)
3458 and then Nkind (Original_Node (H)) = N_Integer_Literal
3459 and then
3460 (Intval (Original_Node (H)) = Uint_0
3461 or else
3462 Intval (Original_Node (H)) = Uint_1)
3463 then
3464 -- Lower bound may in fact be known and known not to exceed
3465 -- upper bound (e.g. reverse 0 .. 1) and that's OK.
3467 if Compile_Time_Known_Value (L)
3468 and then Expr_Value (L) <= Expr_Value (H)
3469 then
3470 null;
3472 -- Otherwise warning is warranted
3474 else
3475 Error_Msg_N ("??loop range may be null", DS);
3476 Error_Msg_N ("\??bounds may be wrong way round", DS);
3477 end if;
3478 end if;
3480 -- Check if either bound is known to be outside the range of the
3481 -- loop parameter type, this is e.g. the case of a loop from
3482 -- 20..X where the type is 1..19.
3484 -- Such a loop is dubious since either it raises CE or it executes
3485 -- zero times, and that cannot be useful!
3487 if Etype (DS) /= Any_Type
3488 and then not Error_Posted (DS)
3489 and then Nkind (DS) = N_Subtype_Indication
3490 and then Nkind (Constraint (DS)) = N_Range_Constraint
3491 then
3492 declare
3493 LLo : constant Node_Id :=
3494 Low_Bound (Range_Expression (Constraint (DS)));
3495 LHi : constant Node_Id :=
3496 High_Bound (Range_Expression (Constraint (DS)));
3498 Bad_Bound : Node_Id := Empty;
3499 -- Suspicious loop bound
3501 begin
3502 -- At this stage L, H are the bounds of the type, and LLo
3503 -- Lhi are the low bound and high bound of the loop.
3505 if Compile_Time_Compare (LLo, L, Assume_Valid => True) = LT
3506 or else
3507 Compile_Time_Compare (LLo, H, Assume_Valid => True) = GT
3508 then
3509 Bad_Bound := LLo;
3510 end if;
3512 if Compile_Time_Compare (LHi, L, Assume_Valid => True) = LT
3513 or else
3514 Compile_Time_Compare (LHi, H, Assume_Valid => True) = GT
3515 then
3516 Bad_Bound := LHi;
3517 end if;
3519 if Present (Bad_Bound) then
3520 Error_Msg_N
3521 ("suspicious loop bound out of range of "
3522 & "loop subtype??", Bad_Bound);
3523 Error_Msg_N
3524 ("\loop executes zero times or raises "
3525 & "Constraint_Error??", Bad_Bound);
3526 end if;
3528 if Compile_Time_Compare (LLo, LHi, Assume_Valid => False)
3529 = GT
3530 then
3531 Error_Msg_N ("??constrained range is null",
3532 Constraint (DS));
3534 -- Additional constraints on modular types can be
3535 -- confusing, add more information.
3537 if Ekind (Etype (DS)) = E_Modular_Integer_Subtype then
3538 Error_Msg_Uint_1 := Intval (LLo);
3539 Error_Msg_Uint_2 := Intval (LHi);
3540 Error_Msg_NE ("\iterator has modular type &, " &
3541 "so the loop has bounds ^ ..^",
3542 Constraint (DS),
3543 Subtype_Mark (DS));
3544 end if;
3546 Set_Is_Null_Loop (Loop_Nod);
3547 Null_Range := True;
3549 -- Suppress other warnings about the body of the loop, as
3550 -- it will never execute.
3551 Set_Suppress_Loop_Warnings (Loop_Nod);
3552 end if;
3553 end;
3554 end if;
3556 -- This declare block is about warnings, if we get an exception while
3557 -- testing for warnings, we simply abandon the attempt silently. This
3558 -- most likely occurs as the result of a previous error, but might
3559 -- just be an obscure case we have missed. In either case, not giving
3560 -- the warning is perfectly acceptable.
3562 exception
3563 when others =>
3564 -- With debug flag K we will get an exception unless an error
3565 -- has already occurred (useful for debugging).
3567 if Debug_Flag_K then
3568 Check_Error_Detected;
3569 end if;
3570 end;
3571 end if;
3573 if Present (Iterator_Filter (N)) then
3574 Analyze_And_Resolve (Iterator_Filter (N), Standard_Boolean);
3575 end if;
3577 -- A loop parameter cannot be effectively volatile (SPARK RM 7.1.3(4)).
3578 -- This check is relevant only when SPARK_Mode is on as it is not a
3579 -- standard Ada legality check.
3581 if SPARK_Mode = On and then Is_Effectively_Volatile (Id) then
3582 Error_Msg_N ("loop parameter cannot be volatile", Id);
3583 end if;
3584 end Analyze_Loop_Parameter_Specification;
3586 ----------------------------
3587 -- Analyze_Loop_Statement --
3588 ----------------------------
3590 procedure Analyze_Loop_Statement (N : Node_Id) is
3592 -- The following exception is raised by routine Prepare_Loop_Statement
3593 -- to avoid further analysis of a transformed loop.
3595 procedure Prepare_Loop_Statement
3596 (Iter : Node_Id;
3597 Stop_Processing : out Boolean);
3598 -- Determine whether loop statement N with iteration scheme Iter must be
3599 -- transformed prior to analysis, and if so, perform it.
3600 -- If Stop_Processing is set to True, should stop further processing.
3602 ----------------------------
3603 -- Prepare_Loop_Statement --
3604 ----------------------------
3606 procedure Prepare_Loop_Statement
3607 (Iter : Node_Id;
3608 Stop_Processing : out Boolean)
3610 function Has_Sec_Stack_Default_Iterator
3611 (Cont_Typ : Entity_Id) return Boolean;
3612 pragma Inline (Has_Sec_Stack_Default_Iterator);
3613 -- Determine whether container type Cont_Typ has a default iterator
3614 -- that requires secondary stack management.
3616 function Is_Sec_Stack_Iteration_Primitive
3617 (Cont_Typ : Entity_Id;
3618 Iter_Prim_Nam : Name_Id) return Boolean;
3619 pragma Inline (Is_Sec_Stack_Iteration_Primitive);
3620 -- Determine whether container type Cont_Typ has an iteration routine
3621 -- described by its name Iter_Prim_Nam that requires secondary stack
3622 -- management.
3624 function Is_Wrapped_In_Block (Stmt : Node_Id) return Boolean;
3625 pragma Inline (Is_Wrapped_In_Block);
3626 -- Determine whether arbitrary statement Stmt is the sole statement
3627 -- wrapped within some block, excluding pragmas.
3629 procedure Prepare_Iterator_Loop
3630 (Iter_Spec : Node_Id;
3631 Stop_Processing : out Boolean);
3632 pragma Inline (Prepare_Iterator_Loop);
3633 -- Prepare an iterator loop with iteration specification Iter_Spec
3634 -- for transformation if needed.
3635 -- If Stop_Processing is set to True, should stop further processing.
3637 procedure Prepare_Param_Spec_Loop
3638 (Param_Spec : Node_Id;
3639 Stop_Processing : out Boolean);
3640 pragma Inline (Prepare_Param_Spec_Loop);
3641 -- Prepare a discrete loop with parameter specification Param_Spec
3642 -- for transformation if needed.
3643 -- If Stop_Processing is set to True, should stop further processing.
3645 procedure Wrap_Loop_Statement (Manage_Sec_Stack : Boolean);
3646 pragma Inline (Wrap_Loop_Statement);
3647 -- Wrap loop statement N within a block. Flag Manage_Sec_Stack must
3648 -- be set when the block must mark and release the secondary stack.
3649 -- Should stop further processing after calling this procedure.
3651 ------------------------------------
3652 -- Has_Sec_Stack_Default_Iterator --
3653 ------------------------------------
3655 function Has_Sec_Stack_Default_Iterator
3656 (Cont_Typ : Entity_Id) return Boolean
3658 Def_Iter : constant Node_Id :=
3659 Find_Value_Of_Aspect
3660 (Cont_Typ, Aspect_Default_Iterator);
3661 begin
3662 return
3663 Present (Def_Iter)
3664 and then Present (Etype (Def_Iter))
3665 and then Requires_Transient_Scope (Etype (Def_Iter));
3666 end Has_Sec_Stack_Default_Iterator;
3668 --------------------------------------
3669 -- Is_Sec_Stack_Iteration_Primitive --
3670 --------------------------------------
3672 function Is_Sec_Stack_Iteration_Primitive
3673 (Cont_Typ : Entity_Id;
3674 Iter_Prim_Nam : Name_Id) return Boolean
3676 Iter_Prim : constant Entity_Id :=
3677 Get_Iterable_Type_Primitive
3678 (Cont_Typ, Iter_Prim_Nam);
3679 begin
3680 return
3681 Present (Iter_Prim)
3682 and then Requires_Transient_Scope (Etype (Iter_Prim));
3683 end Is_Sec_Stack_Iteration_Primitive;
3685 -------------------------
3686 -- Is_Wrapped_In_Block --
3687 -------------------------
3689 function Is_Wrapped_In_Block (Stmt : Node_Id) return Boolean is
3690 Blk_HSS : Node_Id;
3691 Blk_Id : Entity_Id;
3692 Blk_Stmt : Node_Id;
3694 begin
3695 Blk_Id := Current_Scope;
3697 -- The current context is a block. Inspect the statements of the
3698 -- block to determine whether it wraps Stmt.
3700 if Ekind (Blk_Id) = E_Block
3701 and then Present (Block_Node (Blk_Id))
3702 then
3703 Blk_HSS :=
3704 Handled_Statement_Sequence (Parent (Block_Node (Blk_Id)));
3706 -- Skip leading pragmas introduced for invariant and predicate
3707 -- checks.
3709 Blk_Stmt := First (Statements (Blk_HSS));
3710 while Present (Blk_Stmt)
3711 and then Nkind (Blk_Stmt) = N_Pragma
3712 loop
3713 Next (Blk_Stmt);
3714 end loop;
3716 return Blk_Stmt = Stmt and then No (Next (Blk_Stmt));
3717 end if;
3719 return False;
3720 end Is_Wrapped_In_Block;
3722 ---------------------------
3723 -- Prepare_Iterator_Loop --
3724 ---------------------------
3726 procedure Prepare_Iterator_Loop
3727 (Iter_Spec : Node_Id;
3728 Stop_Processing : out Boolean)
3730 Cont_Typ : Entity_Id;
3731 Nam : Node_Id;
3732 Nam_Copy : Node_Id;
3734 begin
3735 Stop_Processing := False;
3737 -- The iterator specification has syntactic errors. Transform the
3738 -- loop into an infinite loop in order to safely perform at least
3739 -- some minor analysis. This check must come first.
3741 if Error_Posted (Iter_Spec) then
3742 Set_Iteration_Scheme (N, Empty);
3743 Analyze (N);
3744 Stop_Processing := True;
3746 -- Nothing to do when the loop is already wrapped in a block
3748 elsif Is_Wrapped_In_Block (N) then
3749 null;
3751 -- Otherwise the iterator loop traverses an array or a container
3752 -- and appears in the form
3754 -- for Def_Id in [reverse] Iterator_Name loop
3755 -- for Def_Id [: Subtyp_Indic] of [reverse] Iterable_Name loop
3757 else
3758 -- Prepare a copy of the iterated name for preanalysis. The
3759 -- copy is semi inserted into the tree by setting its Parent
3760 -- pointer.
3762 Nam := Name (Iter_Spec);
3763 Nam_Copy := New_Copy_Tree (Nam);
3764 Set_Parent (Nam_Copy, Parent (Nam));
3766 -- Determine what the loop is iterating on
3768 Preanalyze_Range (Nam_Copy);
3769 Cont_Typ := Etype (Nam_Copy);
3771 -- The iterator loop is traversing an array. This case does not
3772 -- require any transformation.
3774 if Is_Array_Type (Cont_Typ) then
3775 null;
3777 -- Otherwise unconditionally wrap the loop statement within
3778 -- a block. The expansion of iterator loops may relocate the
3779 -- iterator outside the loop, thus "leaking" its entity into
3780 -- the enclosing scope. Wrapping the loop statement allows
3781 -- for multiple iterator loops using the same iterator name
3782 -- to coexist within the same scope.
3784 -- The block must manage the secondary stack when the iterator
3785 -- loop is traversing a container using either
3787 -- * A default iterator obtained on the secondary stack
3789 -- * Call to Iterate where the iterator is returned on the
3790 -- secondary stack.
3792 -- * Combination of First, Next, and Has_Element where the
3793 -- first two return a cursor on the secondary stack.
3795 else
3796 Wrap_Loop_Statement
3797 (Manage_Sec_Stack =>
3798 Has_Sec_Stack_Default_Iterator (Cont_Typ)
3799 or else Has_Sec_Stack_Call (Nam_Copy)
3800 or else Is_Sec_Stack_Iteration_Primitive
3801 (Cont_Typ, Name_First)
3802 or else Is_Sec_Stack_Iteration_Primitive
3803 (Cont_Typ, Name_Next));
3804 Stop_Processing := True;
3805 end if;
3806 end if;
3807 end Prepare_Iterator_Loop;
3809 -----------------------------
3810 -- Prepare_Param_Spec_Loop --
3811 -----------------------------
3813 procedure Prepare_Param_Spec_Loop
3814 (Param_Spec : Node_Id;
3815 Stop_Processing : out Boolean)
3817 High : Node_Id;
3818 Low : Node_Id;
3819 Rng : Node_Id;
3820 Rng_Copy : Node_Id;
3821 Rng_Typ : Entity_Id;
3823 begin
3824 Stop_Processing := False;
3825 Rng := Discrete_Subtype_Definition (Param_Spec);
3827 -- Nothing to do when the loop is already wrapped in a block
3829 if Is_Wrapped_In_Block (N) then
3830 null;
3832 -- The parameter specification appears in the form
3834 -- for Def_Id in Subtype_Mark Constraint loop
3836 elsif Nkind (Rng) = N_Subtype_Indication
3837 and then Nkind (Range_Expression (Constraint (Rng))) = N_Range
3838 then
3839 Rng := Range_Expression (Constraint (Rng));
3841 -- Preanalyze the bounds of the range constraint, setting
3842 -- parent fields to associate the copied bounds with the range,
3843 -- allowing proper tree climbing during preanalysis.
3845 Low := New_Copy_Tree (Low_Bound (Rng));
3846 High := New_Copy_Tree (High_Bound (Rng));
3848 Set_Parent (Low, Rng);
3849 Set_Parent (High, Rng);
3851 Preanalyze (Low);
3852 Preanalyze (High);
3854 -- The bounds contain at least one function call that returns
3855 -- on the secondary stack. Note that the loop must be wrapped
3856 -- only when such a call exists.
3858 if Has_Sec_Stack_Call (Low) or else Has_Sec_Stack_Call (High)
3859 then
3860 Wrap_Loop_Statement (Manage_Sec_Stack => True);
3861 Stop_Processing := True;
3862 end if;
3864 -- Otherwise the parameter specification appears in the form
3866 -- for Def_Id in Range loop
3868 else
3869 -- Prepare a copy of the discrete range for preanalysis. The
3870 -- copy is semi inserted into the tree by setting its Parent
3871 -- pointer.
3873 Rng_Copy := New_Copy_Tree (Rng);
3874 Set_Parent (Rng_Copy, Parent (Rng));
3876 -- Determine what the loop is iterating on
3878 Preanalyze_Range (Rng_Copy);
3879 Rng_Typ := Etype (Rng_Copy);
3881 -- Wrap the loop statement within a block in order to manage
3882 -- the secondary stack when the discrete range is
3884 -- * Either a Forward_Iterator or a Reverse_Iterator
3886 -- * Function call whose return type requires finalization
3887 -- actions.
3889 -- ??? it is unclear why using Has_Sec_Stack_Call directly on
3890 -- the discrete range causes the freeze node of an itype to be
3891 -- in the wrong scope in complex assertion expressions.
3893 if Is_Iterator (Rng_Typ)
3894 or else (Nkind (Rng_Copy) = N_Function_Call
3895 and then Needs_Finalization (Rng_Typ))
3896 then
3897 Wrap_Loop_Statement (Manage_Sec_Stack => True);
3898 Stop_Processing := True;
3899 end if;
3900 end if;
3901 end Prepare_Param_Spec_Loop;
3903 -------------------------
3904 -- Wrap_Loop_Statement --
3905 -------------------------
3907 procedure Wrap_Loop_Statement (Manage_Sec_Stack : Boolean) is
3908 Loc : constant Source_Ptr := Sloc (N);
3910 Blk : Node_Id;
3911 Blk_Id : Entity_Id;
3913 begin
3914 Blk :=
3915 Make_Block_Statement (Loc,
3916 Declarations => New_List,
3917 Handled_Statement_Sequence =>
3918 Make_Handled_Sequence_Of_Statements (Loc,
3919 Statements => New_List (Relocate_Node (N))));
3921 Add_Block_Identifier (Blk, Blk_Id);
3922 Set_Uses_Sec_Stack (Blk_Id, Manage_Sec_Stack);
3924 Rewrite (N, Blk);
3925 Analyze (N);
3926 end Wrap_Loop_Statement;
3928 -- Local variables
3930 Iter_Spec : constant Node_Id := Iterator_Specification (Iter);
3931 Param_Spec : constant Node_Id := Loop_Parameter_Specification (Iter);
3933 -- Start of processing for Prepare_Loop_Statement
3935 begin
3936 Stop_Processing := False;
3938 if Present (Iter_Spec) then
3939 Prepare_Iterator_Loop (Iter_Spec, Stop_Processing);
3941 elsif Present (Param_Spec) then
3942 Prepare_Param_Spec_Loop (Param_Spec, Stop_Processing);
3943 end if;
3944 end Prepare_Loop_Statement;
3946 -- Local declarations
3948 Id : constant Node_Id := Identifier (N);
3949 Iter : constant Node_Id := Iteration_Scheme (N);
3950 Loc : constant Source_Ptr := Sloc (N);
3951 Ent : Entity_Id;
3952 Stmt : Node_Id;
3954 -- Start of processing for Analyze_Loop_Statement
3956 begin
3957 if Present (Id) then
3959 -- Make name visible, e.g. for use in exit statements. Loop labels
3960 -- are always considered to be referenced.
3962 Analyze (Id);
3963 Ent := Entity (Id);
3965 -- Guard against serious error (typically, a scope mismatch when
3966 -- semantic analysis is requested) by creating loop entity to
3967 -- continue analysis.
3969 if No (Ent) then
3970 if Total_Errors_Detected /= 0 then
3971 Ent := New_Internal_Entity (E_Loop, Current_Scope, Loc, 'L');
3972 else
3973 raise Program_Error;
3974 end if;
3976 -- Verify that the loop name is hot hidden by an unrelated
3977 -- declaration in an inner scope.
3979 elsif Ekind (Ent) /= E_Label and then Ekind (Ent) /= E_Loop then
3980 Error_Msg_Sloc := Sloc (Ent);
3981 Error_Msg_N ("implicit label declaration for & is hidden#", Id);
3983 if Present (Homonym (Ent))
3984 and then Ekind (Homonym (Ent)) = E_Label
3985 then
3986 Set_Entity (Id, Ent);
3987 Mutate_Ekind (Ent, E_Loop);
3988 end if;
3990 else
3991 Generate_Reference (Ent, N, ' ');
3992 Generate_Definition (Ent);
3994 -- If we found a label, mark its type. If not, ignore it, since it
3995 -- means we have a conflicting declaration, which would already
3996 -- have been diagnosed at declaration time. Set Label_Construct
3997 -- of the implicit label declaration, which is not created by the
3998 -- parser for generic units.
4000 if Ekind (Ent) = E_Label then
4001 Reinit_Field_To_Zero (Ent, F_Enclosing_Scope);
4002 Reinit_Field_To_Zero (Ent, F_Reachable);
4003 Mutate_Ekind (Ent, E_Loop);
4005 if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
4006 Set_Label_Construct (Parent (Ent), N);
4007 end if;
4008 end if;
4009 end if;
4011 -- Case of no identifier present. Create one and attach it to the
4012 -- loop statement for use as a scope and as a reference for later
4013 -- expansions. Indicate that the label does not come from source,
4014 -- and attach it to the loop statement so it is part of the tree,
4015 -- even without a full declaration.
4017 else
4018 Ent := New_Internal_Entity (E_Loop, Current_Scope, Loc, 'L');
4019 Set_Etype (Ent, Standard_Void_Type);
4020 Set_Identifier (N, New_Occurrence_Of (Ent, Loc));
4021 Set_Parent (Ent, N);
4022 Set_Has_Created_Identifier (N);
4023 end if;
4025 -- Determine whether the loop statement must be transformed prior to
4026 -- analysis, and if so, perform it. This early modification is needed
4027 -- when:
4029 -- * The loop has an erroneous iteration scheme. In this case the
4030 -- loop is converted into an infinite loop in order to perform
4031 -- minor analysis.
4033 -- * The loop is an Ada 2012 iterator loop. In this case the loop is
4034 -- wrapped within a block to provide a local scope for the iterator.
4035 -- If the iterator specification requires the secondary stack in any
4036 -- way, the block is marked in order to manage it.
4038 -- * The loop is using a parameter specification where the discrete
4039 -- range requires the secondary stack. In this case the loop is
4040 -- wrapped within a block in order to manage the secondary stack.
4042 -- ??? This overlooks finalization: the loop may leave the secondary
4043 -- stack untouched, but its iterator or discrete range may need
4044 -- finalization, in which case the block is also required. Therefore
4045 -- the criterion must be based on Sem_Util.Requires_Transient_Scope,
4046 -- which happens to be what is currently implemented.
4048 if Present (Iter) then
4049 declare
4050 Stop_Processing : Boolean;
4051 begin
4052 Prepare_Loop_Statement (Iter, Stop_Processing);
4054 if Stop_Processing then
4055 return;
4056 end if;
4057 end;
4058 end if;
4060 -- Kill current values on entry to loop, since statements in the body of
4061 -- the loop may have been executed before the loop is entered. Similarly
4062 -- we kill values after the loop, since we do not know that the body of
4063 -- the loop was executed.
4065 Kill_Current_Values;
4066 Push_Scope (Ent);
4067 Analyze_Iteration_Scheme (Iter);
4069 -- Check for following case which merits a warning if the type E of is
4070 -- a multi-dimensional array (and no explicit subscript ranges present).
4072 -- for J in E'Range
4073 -- for K in E'Range
4075 if Present (Iter)
4076 and then Present (Loop_Parameter_Specification (Iter))
4077 then
4078 declare
4079 LPS : constant Node_Id := Loop_Parameter_Specification (Iter);
4080 DSD : constant Node_Id :=
4081 Original_Node (Discrete_Subtype_Definition (LPS));
4082 begin
4083 if Nkind (DSD) = N_Attribute_Reference
4084 and then Attribute_Name (DSD) = Name_Range
4085 and then No (Expressions (DSD))
4086 then
4087 declare
4088 Typ : constant Entity_Id := Etype (Prefix (DSD));
4089 begin
4090 if Is_Array_Type (Typ)
4091 and then Number_Dimensions (Typ) > 1
4092 and then Nkind (Parent (N)) = N_Loop_Statement
4093 and then Present (Iteration_Scheme (Parent (N)))
4094 then
4095 declare
4096 OIter : constant Node_Id :=
4097 Iteration_Scheme (Parent (N));
4098 OLPS : constant Node_Id :=
4099 Loop_Parameter_Specification (OIter);
4100 ODSD : constant Node_Id :=
4101 Original_Node (Discrete_Subtype_Definition (OLPS));
4102 begin
4103 if Nkind (ODSD) = N_Attribute_Reference
4104 and then Attribute_Name (ODSD) = Name_Range
4105 and then No (Expressions (ODSD))
4106 and then Etype (Prefix (ODSD)) = Typ
4107 then
4108 Error_Msg_Sloc := Sloc (ODSD);
4109 Error_Msg_N
4110 ("inner range same as outer range#??", DSD);
4111 end if;
4112 end;
4113 end if;
4114 end;
4115 end if;
4116 end;
4117 end if;
4119 -- Analyze the statements of the body except in the case of an Ada 2012
4120 -- iterator with the expander active. In this case the expander will do
4121 -- a rewrite of the loop into a while loop. We will then analyze the
4122 -- loop body when we analyze this while loop.
4124 -- We need to do this delay because if the container is for indefinite
4125 -- types the actual subtype of the components will only be determined
4126 -- when the cursor declaration is analyzed.
4128 -- If the expander is not active then we want to analyze the loop body
4129 -- now even in the Ada 2012 iterator case, since the rewriting will not
4130 -- be done. Insert the loop variable in the current scope, if not done
4131 -- when analysing the iteration scheme. Set its kind properly to detect
4132 -- improper uses in the loop body.
4134 -- In GNATprove mode, we do one of the above depending on the kind of
4135 -- loop. If it is an iterator over an array, then we do not analyze the
4136 -- loop now. We will analyze it after it has been rewritten by the
4137 -- special SPARK expansion which is activated in GNATprove mode. We need
4138 -- to do this so that other expansions that should occur in GNATprove
4139 -- mode take into account the specificities of the rewritten loop, in
4140 -- particular the introduction of a renaming (which needs to be
4141 -- expanded).
4143 -- In other cases in GNATprove mode then we want to analyze the loop
4144 -- body now, since no rewriting will occur. Within a generic the
4145 -- GNATprove mode is irrelevant, we must analyze the generic for
4146 -- non-local name capture.
4148 if Present (Iter)
4149 and then Present (Iterator_Specification (Iter))
4150 then
4151 if GNATprove_Mode
4152 and then Is_Iterator_Over_Array (Iterator_Specification (Iter))
4153 and then not Inside_A_Generic
4154 then
4155 null;
4157 elsif not Expander_Active then
4158 declare
4159 I_Spec : constant Node_Id := Iterator_Specification (Iter);
4160 Id : constant Entity_Id := Defining_Identifier (I_Spec);
4162 begin
4163 if Scope (Id) /= Current_Scope then
4164 Enter_Name (Id);
4165 end if;
4167 -- In an element iterator, the loop parameter is a variable if
4168 -- the domain of iteration (container or array) is a variable.
4170 if not Of_Present (I_Spec)
4171 or else not Is_Variable (Name (I_Spec))
4172 then
4173 Mutate_Ekind (Id, E_Loop_Parameter);
4174 end if;
4175 end;
4177 Analyze_Statements (Statements (N));
4178 end if;
4180 else
4181 -- Pre-Ada2012 for-loops and while loops
4183 Analyze_Statements (Statements (N));
4184 end if;
4186 -- If the loop has no side effects, mark it for removal.
4188 if Side_Effect_Free_Loop (N) then
4189 Set_Is_Null_Loop (N);
4190 end if;
4192 -- When the iteration scheme of a loop contains attribute 'Loop_Entry,
4193 -- the loop is transformed into a conditional block. Retrieve the loop.
4195 Stmt := N;
4197 if Subject_To_Loop_Entry_Attributes (Stmt) then
4198 Stmt := Find_Loop_In_Conditional_Block (Stmt);
4199 end if;
4201 -- Finish up processing for the loop. We kill all current values, since
4202 -- in general we don't know if the statements in the loop have been
4203 -- executed. We could do a bit better than this with a loop that we
4204 -- know will execute at least once, but it's not worth the trouble and
4205 -- the front end is not in the business of flow tracing.
4207 Process_End_Label (Stmt, 'e', Ent);
4208 End_Scope;
4209 Kill_Current_Values;
4211 -- Check for infinite loop. Skip check for generated code, since it
4212 -- justs waste time and makes debugging the routine called harder.
4214 -- Note that we have to wait till the body of the loop is fully analyzed
4215 -- before making this call, since Check_Infinite_Loop_Warning relies on
4216 -- being able to use semantic visibility information to find references.
4218 if Comes_From_Source (Stmt) then
4219 Check_Infinite_Loop_Warning (Stmt);
4220 end if;
4222 -- Code after loop is unreachable if the loop has no WHILE or FOR and
4223 -- contains no EXIT statements within the body of the loop.
4225 if No (Iter) and then not Has_Exit (Ent) then
4226 Check_Unreachable_Code (Stmt);
4227 end if;
4228 end Analyze_Loop_Statement;
4230 ----------------------------
4231 -- Analyze_Null_Statement --
4232 ----------------------------
4234 -- Note: the semantics of the null statement is implemented by a single
4235 -- null statement, too bad everything isn't as simple as this.
4237 procedure Analyze_Null_Statement (N : Node_Id) is
4238 pragma Warnings (Off, N);
4239 begin
4240 null;
4241 end Analyze_Null_Statement;
4243 -------------------------
4244 -- Analyze_Target_Name --
4245 -------------------------
4247 procedure Analyze_Target_Name (N : Node_Id) is
4248 procedure Report_Error;
4249 -- Complain about illegal use of target_name and rewrite it into unknown
4250 -- identifier.
4252 ------------------
4253 -- Report_Error --
4254 ------------------
4256 procedure Report_Error is
4257 begin
4258 Error_Msg_N
4259 ("must appear in the right-hand side of an assignment statement",
4261 Rewrite (N, New_Occurrence_Of (Any_Id, Sloc (N)));
4262 end Report_Error;
4264 -- Start of processing for Analyze_Target_Name
4266 begin
4267 -- A target name has the type of the left-hand side of the enclosing
4268 -- assignment.
4270 -- First, verify that the context is the right-hand side of an
4271 -- assignment statement.
4273 if No (Current_Assignment) then
4274 Report_Error;
4275 return;
4276 end if;
4278 declare
4279 Current : Node_Id := N;
4280 Context : Node_Id := Parent (N);
4281 begin
4282 while Present (Context) loop
4284 -- Check if target_name appears in the expression of the enclosing
4285 -- assignment.
4287 if Nkind (Context) = N_Assignment_Statement then
4288 if Current = Expression (Context) then
4289 pragma Assert (Context = Current_Assignment);
4290 Set_Etype (N, Etype (Name (Current_Assignment)));
4291 else
4292 Report_Error;
4293 end if;
4294 return;
4296 -- Prevent the search from going too far
4298 elsif Is_Body_Or_Package_Declaration (Context) then
4299 Report_Error;
4300 return;
4301 end if;
4303 Current := Context;
4304 Context := Parent (Context);
4305 end loop;
4307 Report_Error;
4308 end;
4309 end Analyze_Target_Name;
4311 ------------------------
4312 -- Analyze_Statements --
4313 ------------------------
4315 procedure Analyze_Statements (L : List_Id) is
4316 Lab : Entity_Id;
4317 S : Node_Id;
4319 begin
4320 -- The labels declared in the statement list are reachable from
4321 -- statements in the list. We do this as a prepass so that any goto
4322 -- statement will be properly flagged if its target is not reachable.
4323 -- This is not required, but is nice behavior.
4325 S := First (L);
4326 while Present (S) loop
4327 if Nkind (S) = N_Label then
4328 Analyze (Identifier (S));
4329 Lab := Entity (Identifier (S));
4331 -- If we found a label mark it as reachable
4333 if Ekind (Lab) = E_Label then
4334 Generate_Definition (Lab);
4335 Set_Reachable (Lab);
4337 if Nkind (Parent (Lab)) = N_Implicit_Label_Declaration then
4338 Set_Label_Construct (Parent (Lab), S);
4339 end if;
4341 -- If we failed to find a label, it means the implicit declaration
4342 -- of the label was hidden. A for-loop parameter can do this to
4343 -- a label with the same name inside the loop, since the implicit
4344 -- label declaration is in the innermost enclosing body or block
4345 -- statement.
4347 else
4348 Error_Msg_Sloc := Sloc (Lab);
4349 Error_Msg_N
4350 ("implicit label declaration for & is hidden#",
4351 Identifier (S));
4352 end if;
4353 end if;
4355 Next (S);
4356 end loop;
4358 -- Perform semantic analysis on all statements
4360 Conditional_Statements_Begin;
4362 S := First (L);
4363 while Present (S) loop
4364 Analyze (S);
4366 -- Remove dimension in all statements
4368 Remove_Dimension_In_Statement (S);
4369 Next (S);
4370 end loop;
4372 Conditional_Statements_End;
4374 -- Make labels unreachable. Visibility is not sufficient, because labels
4375 -- in one if-branch for example are not reachable from the other branch,
4376 -- even though their declarations are in the enclosing declarative part.
4378 S := First (L);
4379 while Present (S) loop
4380 if Nkind (S) = N_Label
4381 and then Ekind (Entity (Identifier (S))) = E_Label
4382 then
4383 Set_Reachable (Entity (Identifier (S)), False);
4384 end if;
4386 Next (S);
4387 end loop;
4388 end Analyze_Statements;
4390 ----------------------------
4391 -- Check_Unreachable_Code --
4392 ----------------------------
4394 procedure Check_Unreachable_Code (N : Node_Id) is
4396 function Is_Simple_Case (N : Node_Id) return Boolean;
4397 -- N is the condition of an if statement. True if N is simple enough
4398 -- that we should not set Unblocked_Exit_Count in the special case
4399 -- below.
4401 --------------------
4402 -- Is_Simple_Case --
4403 --------------------
4405 function Is_Simple_Case (N : Node_Id) return Boolean is
4406 begin
4407 return
4408 Is_Trivial_Boolean (N)
4409 or else
4410 (Comes_From_Source (N)
4411 and then Is_Static_Expression (N)
4412 and then Nkind (N) in N_Identifier | N_Expanded_Name
4413 and then Ekind (Entity (N)) = E_Constant)
4414 or else
4415 (not In_Instance
4416 and then Nkind (Original_Node (N)) = N_Op_Not
4417 and then Is_Simple_Case (Right_Opnd (Original_Node (N))));
4418 end Is_Simple_Case;
4420 Error_Node : Node_Id;
4421 Nxt : Node_Id;
4422 P : Node_Id;
4424 begin
4425 if Comes_From_Source (N) then
4426 Nxt := Original_Node (Next (N));
4428 -- Skip past pragmas
4430 while Nkind (Nxt) = N_Pragma loop
4431 Nxt := Original_Node (Next (Nxt));
4432 end loop;
4434 -- If a label follows us, then we never have dead code, since someone
4435 -- could branch to the label, so we just ignore it.
4437 if Nkind (Nxt) = N_Label then
4438 return;
4440 -- Otherwise see if we have a real statement following us
4442 elsif Comes_From_Source (Nxt)
4443 and then Is_Statement (Nxt)
4444 then
4445 -- Special very annoying exception. Ada RM 6.5(5) annoyingly
4446 -- requires functions to have at least one return statement, so
4447 -- don't complain about a simple return that follows a raise or a
4448 -- call to procedure with No_Return.
4450 if not (Present (Current_Subprogram)
4451 and then Ekind (Current_Subprogram) = E_Function
4452 and then (Nkind (N) in N_Raise_Statement
4453 or else
4454 (Nkind (N) = N_Procedure_Call_Statement
4455 and then Is_Entity_Name (Name (N))
4456 and then Present (Entity (Name (N)))
4457 and then No_Return (Entity (Name (N)))))
4458 and then Nkind (Nxt) = N_Simple_Return_Statement)
4459 then
4460 -- The rather strange shenanigans with the warning message
4461 -- here reflects the fact that Kill_Dead_Code is very good at
4462 -- removing warnings in deleted code, and this is one warning
4463 -- we would prefer NOT to have removed.
4465 Error_Node := Nxt;
4467 -- If we have unreachable code, analyze and remove the
4468 -- unreachable code, since it is useless and we don't want
4469 -- to generate junk warnings.
4471 -- We skip this step if we are not in code generation mode.
4473 -- This is the one case where we remove dead code in the
4474 -- semantics as opposed to the expander, and we do not want
4475 -- to remove code if we are not in code generation mode, since
4476 -- this messes up the tree or loses useful information for
4477 -- analysis tools such as CodePeer.
4479 -- Note that one might react by moving the whole circuit to
4480 -- exp_ch5, but then we lose the warning in -gnatc mode.
4482 if Operating_Mode = Generate_Code then
4483 loop
4484 declare
4485 Del : constant Node_Id := Next (N);
4486 -- Node to be possibly deleted
4487 begin
4488 -- Quit deleting when we have nothing more to delete
4489 -- or if we hit a label (since someone could transfer
4490 -- control to a label, so we should not delete it).
4492 exit when No (Del) or else Nkind (Del) = N_Label;
4494 -- Statement/declaration is to be deleted
4496 Analyze (Del);
4497 Kill_Dead_Code (Del);
4498 Remove (Del);
4499 end;
4500 end loop;
4502 -- If this is a function, we add "raise Program_Error;",
4503 -- because otherwise, we will get incorrect warnings about
4504 -- falling off the end of the function.
4506 declare
4507 Subp : constant Entity_Id := Current_Subprogram;
4508 begin
4509 if Present (Subp) and then Ekind (Subp) = E_Function then
4510 Insert_After_And_Analyze (N,
4511 Make_Raise_Program_Error (Sloc (Error_Node),
4512 Reason => PE_Missing_Return));
4513 end if;
4514 end;
4516 end if;
4518 -- Suppress the warning in instances, because a statement can
4519 -- be unreachable in some instances but not others.
4521 if not In_Instance then
4522 Error_Msg_N ("??unreachable code!", Error_Node);
4523 end if;
4524 end if;
4526 -- If the unconditional transfer of control instruction is the
4527 -- last statement of a sequence, then see if our parent is one of
4528 -- the constructs for which we count unblocked exits, and if so,
4529 -- adjust the count.
4531 else
4532 P := Parent (N);
4534 -- Statements in THEN part or ELSE part of IF statement
4536 if Nkind (P) = N_If_Statement then
4537 null;
4539 -- Statements in ELSIF part of an IF statement
4541 elsif Nkind (P) = N_Elsif_Part then
4542 P := Parent (P);
4543 pragma Assert (Nkind (P) = N_If_Statement);
4545 -- Statements in CASE statement alternative
4547 elsif Nkind (P) = N_Case_Statement_Alternative then
4548 P := Parent (P);
4549 pragma Assert (Nkind (P) = N_Case_Statement);
4551 -- Statements in body of block
4553 elsif Nkind (P) = N_Handled_Sequence_Of_Statements
4554 and then Nkind (Parent (P)) = N_Block_Statement
4555 then
4556 -- The original loop is now placed inside a block statement
4557 -- due to the expansion of attribute 'Loop_Entry. Return as
4558 -- this is not a "real" block for the purposes of exit
4559 -- counting.
4561 if Nkind (N) = N_Loop_Statement
4562 and then Subject_To_Loop_Entry_Attributes (N)
4563 then
4564 return;
4565 end if;
4567 -- Statements in exception handler in a block
4569 elsif Nkind (P) = N_Exception_Handler
4570 and then Nkind (Parent (P)) = N_Handled_Sequence_Of_Statements
4571 and then Nkind (Parent (Parent (P))) = N_Block_Statement
4572 then
4573 null;
4575 -- None of these cases, so return
4577 else
4578 return;
4579 end if;
4581 -- This was one of the cases we are looking for (i.e. the parent
4582 -- construct was IF, CASE or block). In most cases, we simply
4583 -- decrement the count. However, if the parent is something like:
4585 -- if cond then
4586 -- raise ...; -- or some other jump
4587 -- end if;
4589 -- where cond is an expression that is known-true at compile time,
4590 -- we can treat that as just the jump -- i.e. anything following
4591 -- the if statement is unreachable. We don't do this for simple
4592 -- cases like "if True" or "if Debug_Flag", because that causes
4593 -- too many warnings.
4595 if Nkind (P) = N_If_Statement
4596 and then Present (Then_Statements (P))
4597 and then No (Elsif_Parts (P))
4598 and then No (Else_Statements (P))
4599 and then Is_OK_Static_Expression (Condition (P))
4600 and then Is_True (Expr_Value (Condition (P)))
4601 and then not Is_Simple_Case (Condition (P))
4602 then
4603 pragma Assert (Unblocked_Exit_Count = 2);
4604 Unblocked_Exit_Count := 0;
4605 else
4606 Unblocked_Exit_Count := Unblocked_Exit_Count - 1;
4607 end if;
4608 end if;
4609 end if;
4610 end Check_Unreachable_Code;
4612 ------------------------
4613 -- Has_Sec_Stack_Call --
4614 ------------------------
4616 function Has_Sec_Stack_Call (N : Node_Id) return Boolean is
4617 function Check_Call (N : Node_Id) return Traverse_Result;
4618 -- Check if N is a function call which uses the secondary stack
4620 ----------------
4621 -- Check_Call --
4622 ----------------
4624 function Check_Call (N : Node_Id) return Traverse_Result is
4625 Nam : Node_Id;
4626 Subp : Entity_Id;
4627 Typ : Entity_Id;
4629 begin
4630 if Nkind (N) = N_Function_Call then
4631 Nam := Name (N);
4633 -- Obtain the subprogram being invoked
4635 loop
4636 if Nkind (Nam) = N_Explicit_Dereference then
4637 Nam := Prefix (Nam);
4639 elsif Nkind (Nam) = N_Selected_Component then
4640 Nam := Selector_Name (Nam);
4642 else
4643 exit;
4644 end if;
4645 end loop;
4647 Subp := Entity (Nam);
4649 if Present (Subp) then
4650 Typ := Etype (Subp);
4652 if Requires_Transient_Scope (Typ) then
4653 return Abandon;
4655 elsif Sec_Stack_Needed_For_Return (Subp) then
4656 return Abandon;
4657 end if;
4658 end if;
4659 end if;
4661 -- Continue traversing the tree
4663 return OK;
4664 end Check_Call;
4666 function Check_Calls is new Traverse_Func (Check_Call);
4668 -- Start of processing for Has_Sec_Stack_Call
4670 begin
4671 return Check_Calls (N) = Abandon;
4672 end Has_Sec_Stack_Call;
4674 ----------------------
4675 -- Preanalyze_Range --
4676 ----------------------
4678 procedure Preanalyze_Range (R_Copy : Node_Id) is
4679 Save_Analysis : constant Boolean := Full_Analysis;
4680 Typ : Entity_Id;
4682 begin
4683 Full_Analysis := False;
4684 Expander_Mode_Save_And_Set (False);
4686 -- In addition to the above we must explicitly suppress the generation
4687 -- of freeze nodes that might otherwise be generated during resolution
4688 -- of the range (e.g. if given by an attribute that will freeze its
4689 -- prefix).
4691 Set_Must_Not_Freeze (R_Copy);
4693 if Nkind (R_Copy) = N_Attribute_Reference then
4694 Set_Must_Not_Freeze (Prefix (R_Copy));
4695 end if;
4697 Analyze (R_Copy);
4699 if Nkind (R_Copy) in N_Subexpr and then Is_Overloaded (R_Copy) then
4701 -- Apply preference rules for range of predefined integer types, or
4702 -- check for array or iterable construct for "of" iterator, or
4703 -- diagnose true ambiguity.
4705 declare
4706 I : Interp_Index;
4707 It : Interp;
4708 Found : Entity_Id := Empty;
4710 begin
4711 Get_First_Interp (R_Copy, I, It);
4712 while Present (It.Typ) loop
4713 if Is_Discrete_Type (It.Typ) then
4714 if No (Found) then
4715 Found := It.Typ;
4716 else
4717 if Scope (Found) = Standard_Standard then
4718 null;
4720 elsif Scope (It.Typ) = Standard_Standard then
4721 Found := It.Typ;
4723 else
4724 -- Both of them are user-defined
4726 Error_Msg_N
4727 ("ambiguous bounds in range of iteration", R_Copy);
4728 Error_Msg_N ("\possible interpretations:", R_Copy);
4729 Error_Msg_NE ("\\}", R_Copy, Found);
4730 Error_Msg_NE ("\\}", R_Copy, It.Typ);
4731 exit;
4732 end if;
4733 end if;
4735 elsif Nkind (Parent (R_Copy)) = N_Iterator_Specification
4736 and then Of_Present (Parent (R_Copy))
4737 then
4738 if Is_Array_Type (It.Typ)
4739 or else Has_Aspect (It.Typ, Aspect_Iterator_Element)
4740 or else Has_Aspect (It.Typ, Aspect_Constant_Indexing)
4741 or else Has_Aspect (It.Typ, Aspect_Variable_Indexing)
4742 then
4743 if No (Found) then
4744 Found := It.Typ;
4745 Set_Etype (R_Copy, It.Typ);
4747 else
4748 Error_Msg_N ("ambiguous domain of iteration", R_Copy);
4749 end if;
4750 end if;
4751 end if;
4753 Get_Next_Interp (I, It);
4754 end loop;
4755 end;
4756 end if;
4758 -- Subtype mark in iteration scheme
4760 if Is_Entity_Name (R_Copy) and then Is_Type (Entity (R_Copy)) then
4761 null;
4763 -- Expression in range, or Ada 2012 iterator
4765 elsif Nkind (R_Copy) in N_Subexpr then
4766 Resolve (R_Copy);
4767 Typ := Etype (R_Copy);
4769 if Is_Discrete_Type (Typ) then
4770 null;
4772 -- Check that the resulting object is an iterable container
4774 elsif Has_Aspect (Typ, Aspect_Iterator_Element)
4775 or else Has_Aspect (Typ, Aspect_Constant_Indexing)
4776 or else Has_Aspect (Typ, Aspect_Variable_Indexing)
4777 then
4778 null;
4780 -- The expression may yield an implicit reference to an iterable
4781 -- container. Insert explicit dereference so that proper type is
4782 -- visible in the loop.
4784 elsif Has_Implicit_Dereference (Etype (R_Copy)) then
4785 Build_Explicit_Dereference
4786 (R_Copy, Get_Reference_Discriminant (Etype (R_Copy)));
4787 end if;
4788 end if;
4790 Expander_Mode_Restore;
4791 Full_Analysis := Save_Analysis;
4792 end Preanalyze_Range;
4794 end Sem_Ch5;