[NDS32] new attribute no_prologue and new option -mret-in-naked-func.
[official-gcc.git] / gcc / ada / sem_ch5.adb
blobf18fd4089f40293d9743d09ac2f4b2339bd6a36a
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-2018, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Aspects; use Aspects;
27 with Atree; use Atree;
28 with Checks; use Checks;
29 with Einfo; use Einfo;
30 with Errout; use Errout;
31 with Expander; use Expander;
32 with Exp_Ch6; use Exp_Ch6;
33 with Exp_Util; use Exp_Util;
34 with Freeze; use Freeze;
35 with Ghost; use Ghost;
36 with Lib; use Lib;
37 with Lib.Xref; use Lib.Xref;
38 with Namet; use Namet;
39 with Nlists; use Nlists;
40 with Nmake; use Nmake;
41 with Opt; use Opt;
42 with Restrict; use Restrict;
43 with Rident; use Rident;
44 with Sem; use Sem;
45 with Sem_Aux; use Sem_Aux;
46 with Sem_Case; use Sem_Case;
47 with Sem_Ch3; use Sem_Ch3;
48 with Sem_Ch6; use Sem_Ch6;
49 with Sem_Ch8; use Sem_Ch8;
50 with Sem_Dim; use Sem_Dim;
51 with Sem_Disp; use Sem_Disp;
52 with Sem_Elab; use Sem_Elab;
53 with Sem_Eval; use Sem_Eval;
54 with Sem_Res; use Sem_Res;
55 with Sem_Type; use Sem_Type;
56 with Sem_Util; use Sem_Util;
57 with Sem_Warn; use Sem_Warn;
58 with Snames; use Snames;
59 with Stand; use Stand;
60 with Sinfo; use Sinfo;
61 with Targparm; use Targparm;
62 with Tbuild; use Tbuild;
63 with Uintp; use Uintp;
65 package body Sem_Ch5 is
67 Current_Assignment : Node_Id := Empty;
68 -- This variable holds the node for an assignment that contains target
69 -- names. The corresponding flag has been set by the parser, and when
70 -- set the analysis of the RHS must be done with all expansion disabled,
71 -- because the assignment is reanalyzed after expansion has replaced all
72 -- occurrences of the target name appropriately.
74 Unblocked_Exit_Count : Nat := 0;
75 -- This variable is used when processing if statements, case statements,
76 -- and block statements. It counts the number of exit points that are not
77 -- blocked by unconditional transfer instructions: for IF and CASE, these
78 -- are the branches of the conditional; for a block, they are the statement
79 -- sequence of the block, and the statement sequences of any exception
80 -- handlers that are part of the block. When processing is complete, if
81 -- this count is zero, it means that control cannot fall through the IF,
82 -- CASE or block statement. This is used for the generation of warning
83 -- messages. This variable is recursively saved on entry to processing the
84 -- construct, and restored on exit.
86 procedure Preanalyze_Range (R_Copy : Node_Id);
87 -- Determine expected type of range or domain of iteration of Ada 2012
88 -- loop by analyzing separate copy. Do the analysis and resolution of the
89 -- copy of the bound(s) with expansion disabled, to prevent the generation
90 -- of finalization actions. This prevents memory leaks when the bounds
91 -- contain calls to functions returning controlled arrays or when the
92 -- domain of iteration is a container.
94 ------------------------
95 -- Analyze_Assignment --
96 ------------------------
98 -- WARNING: This routine manages Ghost regions. Return statements must be
99 -- replaced by gotos which jump to the end of the routine and restore the
100 -- Ghost mode.
102 procedure Analyze_Assignment (N : Node_Id) is
103 Lhs : constant Node_Id := Name (N);
104 Rhs : Node_Id := Expression (N);
106 procedure Diagnose_Non_Variable_Lhs (N : Node_Id);
107 -- N is the node for the left hand side of an assignment, and it is not
108 -- a variable. This routine issues an appropriate diagnostic.
110 function Is_Protected_Part_Of_Constituent
111 (Nod : Node_Id) return Boolean;
112 -- Determine whether arbitrary node Nod denotes a Part_Of constituent of
113 -- a single protected type.
115 procedure Kill_Lhs;
116 -- This is called to kill current value settings of a simple variable
117 -- on the left hand side. We call it if we find any error in analyzing
118 -- the assignment, and at the end of processing before setting any new
119 -- current values in place.
121 procedure Set_Assignment_Type
122 (Opnd : Node_Id;
123 Opnd_Type : in out Entity_Id);
124 -- Opnd is either the Lhs or Rhs of the assignment, and Opnd_Type is the
125 -- nominal subtype. This procedure is used to deal with cases where the
126 -- nominal subtype must be replaced by the actual subtype.
128 procedure Transform_BIP_Assignment (Typ : Entity_Id);
129 function Should_Transform_BIP_Assignment
130 (Typ : Entity_Id) return Boolean;
131 -- If the right-hand side of an assignment statement is a build-in-place
132 -- call we cannot build in place, so we insert a temp initialized with
133 -- the call, and transform the assignment statement to copy the temp.
134 -- Transform_BIP_Assignment does the tranformation, and
135 -- Should_Transform_BIP_Assignment determines whether we should.
136 -- The same goes for qualified expressions and conversions whose
137 -- operand is such a call.
139 -- This is only for nonlimited types; assignment statements are illegal
140 -- for limited types, but are generated internally for aggregates and
141 -- init procs. These limited-type are not really assignment statements
142 -- -- conceptually, they are initializations, so should not be
143 -- transformed.
145 -- Similarly, for nonlimited types, aggregates and init procs generate
146 -- assignment statements that are really initializations. These are
147 -- marked No_Ctrl_Actions.
149 function Within_Function return Boolean;
150 -- Determine whether the current scope is a function or appears within
151 -- one.
153 -------------------------------
154 -- Diagnose_Non_Variable_Lhs --
155 -------------------------------
157 procedure Diagnose_Non_Variable_Lhs (N : Node_Id) is
158 begin
159 -- Not worth posting another error if left hand side already flagged
160 -- as being illegal in some respect.
162 if Error_Posted (N) then
163 return;
165 -- Some special bad cases of entity names
167 elsif Is_Entity_Name (N) then
168 declare
169 Ent : constant Entity_Id := Entity (N);
171 begin
172 if Ekind (Ent) = E_In_Parameter then
173 Error_Msg_N
174 ("assignment to IN mode parameter not allowed", N);
175 return;
177 -- Renamings of protected private components are turned into
178 -- constants when compiling a protected function. In the case
179 -- of single protected types, the private component appears
180 -- directly.
182 elsif (Is_Prival (Ent) and then Within_Function)
183 or else
184 (Ekind (Ent) = E_Component
185 and then Is_Protected_Type (Scope (Ent)))
186 then
187 Error_Msg_N
188 ("protected function cannot modify protected object", N);
189 return;
191 elsif Ekind (Ent) = E_Loop_Parameter then
192 Error_Msg_N ("assignment to loop parameter not allowed", N);
193 return;
194 end if;
195 end;
197 -- For indexed components, test prefix if it is in array. We do not
198 -- want to recurse for cases where the prefix is a pointer, since we
199 -- may get a message confusing the pointer and what it references.
201 elsif Nkind (N) = N_Indexed_Component
202 and then Is_Array_Type (Etype (Prefix (N)))
203 then
204 Diagnose_Non_Variable_Lhs (Prefix (N));
205 return;
207 -- Another special case for assignment to discriminant
209 elsif Nkind (N) = N_Selected_Component then
210 if Present (Entity (Selector_Name (N)))
211 and then Ekind (Entity (Selector_Name (N))) = E_Discriminant
212 then
213 Error_Msg_N ("assignment to discriminant not allowed", N);
214 return;
216 -- For selection from record, diagnose prefix, but note that again
217 -- we only do this for a record, not e.g. for a pointer.
219 elsif Is_Record_Type (Etype (Prefix (N))) then
220 Diagnose_Non_Variable_Lhs (Prefix (N));
221 return;
222 end if;
223 end if;
225 -- If we fall through, we have no special message to issue
227 Error_Msg_N ("left hand side of assignment must be a variable", N);
228 end Diagnose_Non_Variable_Lhs;
230 --------------------------------------
231 -- Is_Protected_Part_Of_Constituent --
232 --------------------------------------
234 function Is_Protected_Part_Of_Constituent
235 (Nod : Node_Id) return Boolean
237 Encap_Id : Entity_Id;
238 Var_Id : Entity_Id;
240 begin
241 -- Abstract states and variables may act as Part_Of constituents of
242 -- single protected types, however only variables can be modified by
243 -- an assignment.
245 if Is_Entity_Name (Nod) then
246 Var_Id := Entity (Nod);
248 if Present (Var_Id) and then Ekind (Var_Id) = E_Variable then
249 Encap_Id := Encapsulating_State (Var_Id);
251 -- To qualify, the node must denote a reference to a variable
252 -- whose encapsulating state is a single protected object.
254 return
255 Present (Encap_Id)
256 and then Is_Single_Protected_Object (Encap_Id);
257 end if;
258 end if;
260 return False;
261 end Is_Protected_Part_Of_Constituent;
263 --------------
264 -- Kill_Lhs --
265 --------------
267 procedure Kill_Lhs is
268 begin
269 if Is_Entity_Name (Lhs) then
270 declare
271 Ent : constant Entity_Id := Entity (Lhs);
272 begin
273 if Present (Ent) then
274 Kill_Current_Values (Ent);
275 end if;
276 end;
277 end if;
278 end Kill_Lhs;
280 -------------------------
281 -- Set_Assignment_Type --
282 -------------------------
284 procedure Set_Assignment_Type
285 (Opnd : Node_Id;
286 Opnd_Type : in out Entity_Id)
288 Decl : Node_Id;
290 begin
291 Require_Entity (Opnd);
293 -- If the assignment operand is an in-out or out parameter, then we
294 -- get the actual subtype (needed for the unconstrained case). If the
295 -- operand is the actual in an entry declaration, then within the
296 -- accept statement it is replaced with a local renaming, which may
297 -- also have an actual subtype.
299 if Is_Entity_Name (Opnd)
300 and then (Ekind (Entity (Opnd)) = E_Out_Parameter
301 or else Ekind_In (Entity (Opnd),
302 E_In_Out_Parameter,
303 E_Generic_In_Out_Parameter)
304 or else
305 (Ekind (Entity (Opnd)) = E_Variable
306 and then Nkind (Parent (Entity (Opnd))) =
307 N_Object_Renaming_Declaration
308 and then Nkind (Parent (Parent (Entity (Opnd)))) =
309 N_Accept_Statement))
310 then
311 Opnd_Type := Get_Actual_Subtype (Opnd);
313 -- If assignment operand is a component reference, then we get the
314 -- actual subtype of the component for the unconstrained case.
316 elsif Nkind_In (Opnd, N_Selected_Component, N_Explicit_Dereference)
317 and then not Is_Unchecked_Union (Opnd_Type)
318 then
319 Decl := Build_Actual_Subtype_Of_Component (Opnd_Type, Opnd);
321 if Present (Decl) then
322 Insert_Action (N, Decl);
323 Mark_Rewrite_Insertion (Decl);
324 Analyze (Decl);
325 Opnd_Type := Defining_Identifier (Decl);
326 Set_Etype (Opnd, Opnd_Type);
327 Freeze_Itype (Opnd_Type, N);
329 elsif Is_Constrained (Etype (Opnd)) then
330 Opnd_Type := Etype (Opnd);
331 end if;
333 -- For slice, use the constrained subtype created for the slice
335 elsif Nkind (Opnd) = N_Slice then
336 Opnd_Type := Etype (Opnd);
337 end if;
338 end Set_Assignment_Type;
340 -------------------------------------
341 -- Should_Transform_BIP_Assignment --
342 -------------------------------------
344 function Should_Transform_BIP_Assignment
345 (Typ : Entity_Id) return Boolean
347 Result : Boolean;
349 begin
350 if Expander_Active
351 and then not Is_Limited_View (Typ)
352 and then Is_Build_In_Place_Result_Type (Typ)
353 and then not No_Ctrl_Actions (N)
354 then
355 -- This function is called early, before name resolution is
356 -- complete, so we have to deal with things that might turn into
357 -- function calls later. N_Function_Call and N_Op nodes are the
358 -- obvious case. An N_Identifier or N_Expanded_Name is a
359 -- parameterless function call if it denotes a function.
360 -- Finally, an attribute reference can be a function call.
362 case Nkind (Unqual_Conv (Rhs)) is
363 when N_Function_Call
364 | N_Op
366 Result := True;
368 when N_Expanded_Name
369 | N_Identifier
371 case Ekind (Entity (Unqual_Conv (Rhs))) is
372 when E_Function
373 | E_Operator
375 Result := True;
377 when others =>
378 Result := False;
379 end case;
381 when N_Attribute_Reference =>
382 Result := Attribute_Name (Unqual_Conv (Rhs)) = Name_Input;
383 -- T'Input will turn into a call whose result type is T
385 when others =>
386 Result := False;
387 end case;
388 else
389 Result := False;
390 end if;
392 return Result;
393 end Should_Transform_BIP_Assignment;
395 ------------------------------
396 -- Transform_BIP_Assignment --
397 ------------------------------
399 procedure Transform_BIP_Assignment (Typ : Entity_Id) is
401 -- Tranform "X : [constant] T := F (...);" into:
403 -- Temp : constant T := F (...);
404 -- X := Temp;
406 Loc : constant Source_Ptr := Sloc (N);
407 Def_Id : constant Entity_Id := Make_Temporary (Loc, 'Y', Rhs);
408 Obj_Decl : constant Node_Id :=
409 Make_Object_Declaration (Loc,
410 Defining_Identifier => Def_Id,
411 Constant_Present => True,
412 Object_Definition => New_Occurrence_Of (Typ, Loc),
413 Expression => Rhs,
414 Has_Init_Expression => True);
416 begin
417 Set_Etype (Def_Id, Typ);
418 Set_Expression (N, New_Occurrence_Of (Def_Id, Loc));
420 -- At this point, Rhs is no longer equal to Expression (N), so:
422 Rhs := Expression (N);
424 Insert_Action (N, Obj_Decl);
425 end Transform_BIP_Assignment;
427 ---------------------
428 -- Within_Function --
429 ---------------------
431 function Within_Function return Boolean is
432 Scop_Id : constant Entity_Id := Current_Scope;
434 begin
435 if Ekind (Scop_Id) = E_Function then
436 return True;
438 elsif Ekind (Enclosing_Dynamic_Scope (Scop_Id)) = E_Function then
439 return True;
440 end if;
442 return False;
443 end Within_Function;
445 -- Local variables
447 T1 : Entity_Id;
448 T2 : Entity_Id;
450 Save_Full_Analysis : Boolean := False;
451 -- Force initialization to facilitate static analysis
453 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
454 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
455 -- Save the Ghost-related attributes to restore on exit
457 -- Start of processing for Analyze_Assignment
459 begin
460 Mark_Coextensions (N, Rhs);
462 -- Preserve relevant elaboration-related attributes of the context which
463 -- are no longer available or very expensive to recompute once analysis,
464 -- resolution, and expansion are over.
466 Mark_Elaboration_Attributes
467 (N_Id => N,
468 Checks => True,
469 Modes => True);
471 -- Analyze the target of the assignment first in case the expression
472 -- contains references to Ghost entities. The checks that verify the
473 -- proper use of a Ghost entity need to know the enclosing context.
475 Analyze (Lhs);
477 -- An assignment statement is Ghost when the left hand side denotes a
478 -- Ghost entity. Set the mode now to ensure that any nodes generated
479 -- during analysis and expansion are properly marked as Ghost.
481 if Has_Target_Names (N) then
482 Current_Assignment := N;
483 Expander_Mode_Save_And_Set (False);
484 Save_Full_Analysis := Full_Analysis;
485 Full_Analysis := False;
486 else
487 Current_Assignment := Empty;
488 end if;
490 Mark_And_Set_Ghost_Assignment (N);
491 Analyze (Rhs);
493 -- Ensure that we never do an assignment on a variable marked as
494 -- Is_Safe_To_Reevaluate.
496 pragma Assert
497 (not Is_Entity_Name (Lhs)
498 or else Ekind (Entity (Lhs)) /= E_Variable
499 or else not Is_Safe_To_Reevaluate (Entity (Lhs)));
501 -- Start type analysis for assignment
503 T1 := Etype (Lhs);
505 -- In the most general case, both Lhs and Rhs can be overloaded, and we
506 -- must compute the intersection of the possible types on each side.
508 if Is_Overloaded (Lhs) then
509 declare
510 I : Interp_Index;
511 It : Interp;
513 begin
514 T1 := Any_Type;
515 Get_First_Interp (Lhs, I, It);
517 while Present (It.Typ) loop
519 -- An indexed component with generalized indexing is always
520 -- overloaded with the corresponding dereference. Discard the
521 -- interpretation that yields a reference type, which is not
522 -- assignable.
524 if Nkind (Lhs) = N_Indexed_Component
525 and then Present (Generalized_Indexing (Lhs))
526 and then Has_Implicit_Dereference (It.Typ)
527 then
528 null;
530 -- This may be a call to a parameterless function through an
531 -- implicit dereference, so discard interpretation as well.
533 elsif Is_Entity_Name (Lhs)
534 and then Has_Implicit_Dereference (It.Typ)
535 then
536 null;
538 elsif Has_Compatible_Type (Rhs, It.Typ) then
539 if T1 = Any_Type then
540 T1 := It.Typ;
541 else
542 -- An explicit dereference is overloaded if the prefix
543 -- is. Try to remove the ambiguity on the prefix, the
544 -- error will be posted there if the ambiguity is real.
546 if Nkind (Lhs) = N_Explicit_Dereference then
547 declare
548 PI : Interp_Index;
549 PI1 : Interp_Index := 0;
550 PIt : Interp;
551 Found : Boolean;
553 begin
554 Found := False;
555 Get_First_Interp (Prefix (Lhs), PI, PIt);
557 while Present (PIt.Typ) loop
558 if Is_Access_Type (PIt.Typ)
559 and then Has_Compatible_Type
560 (Rhs, Designated_Type (PIt.Typ))
561 then
562 if Found then
563 PIt :=
564 Disambiguate (Prefix (Lhs),
565 PI1, PI, Any_Type);
567 if PIt = No_Interp then
568 Error_Msg_N
569 ("ambiguous left-hand side in "
570 & "assignment", Lhs);
571 exit;
572 else
573 Resolve (Prefix (Lhs), PIt.Typ);
574 end if;
576 exit;
577 else
578 Found := True;
579 PI1 := PI;
580 end if;
581 end if;
583 Get_Next_Interp (PI, PIt);
584 end loop;
585 end;
587 else
588 Error_Msg_N
589 ("ambiguous left-hand side in assignment", Lhs);
590 exit;
591 end if;
592 end if;
593 end if;
595 Get_Next_Interp (I, It);
596 end loop;
597 end;
599 if T1 = Any_Type then
600 Error_Msg_N
601 ("no valid types for left-hand side for assignment", Lhs);
602 Kill_Lhs;
603 goto Leave;
604 end if;
605 end if;
607 -- Deal with build-in-place calls for nonlimited types. We don't do this
608 -- later, because resolving the rhs tranforms it incorrectly for build-
609 -- in-place.
611 if Should_Transform_BIP_Assignment (Typ => T1) then
613 -- In certain cases involving user-defined concatenation operators,
614 -- we need to resolve the right-hand side before transforming the
615 -- assignment.
617 case Nkind (Unqual_Conv (Rhs)) is
618 when N_Function_Call =>
619 declare
620 Actual : Node_Id :=
621 First (Parameter_Associations (Unqual_Conv (Rhs)));
622 Actual_Exp : Node_Id;
624 begin
625 while Present (Actual) loop
626 if Nkind (Actual) = N_Parameter_Association then
627 Actual_Exp := Explicit_Actual_Parameter (Actual);
628 else
629 Actual_Exp := Actual;
630 end if;
632 if Nkind (Actual_Exp) = N_Op_Concat then
633 Resolve (Rhs, T1);
634 exit;
635 end if;
637 Next (Actual);
638 end loop;
639 end;
641 when N_Attribute_Reference
642 | N_Expanded_Name
643 | N_Identifier
644 | N_Op
646 null;
648 when others =>
649 raise Program_Error;
650 end case;
652 Transform_BIP_Assignment (Typ => T1);
653 end if;
655 pragma Assert (not Should_Transform_BIP_Assignment (Typ => T1));
657 -- The resulting assignment type is T1, so now we will resolve the left
658 -- hand side of the assignment using this determined type.
660 Resolve (Lhs, T1);
662 -- Cases where Lhs is not a variable. In an instance or an inlined body
663 -- no need for further check because assignment was legal in template.
665 if In_Inlined_Body then
666 null;
668 elsif not Is_Variable (Lhs) then
670 -- Ada 2005 (AI-327): Check assignment to the attribute Priority of a
671 -- protected object.
673 declare
674 Ent : Entity_Id;
675 S : Entity_Id;
677 begin
678 if Ada_Version >= Ada_2005 then
680 -- Handle chains of renamings
682 Ent := Lhs;
683 while Nkind (Ent) in N_Has_Entity
684 and then Present (Entity (Ent))
685 and then Present (Renamed_Object (Entity (Ent)))
686 loop
687 Ent := Renamed_Object (Entity (Ent));
688 end loop;
690 if (Nkind (Ent) = N_Attribute_Reference
691 and then Attribute_Name (Ent) = Name_Priority)
693 -- Renamings of the attribute Priority applied to protected
694 -- objects have been previously expanded into calls to the
695 -- Get_Ceiling run-time subprogram.
697 or else Is_Expanded_Priority_Attribute (Ent)
698 then
699 -- The enclosing subprogram cannot be a protected function
701 S := Current_Scope;
702 while not (Is_Subprogram (S)
703 and then Convention (S) = Convention_Protected)
704 and then S /= Standard_Standard
705 loop
706 S := Scope (S);
707 end loop;
709 if Ekind (S) = E_Function
710 and then Convention (S) = Convention_Protected
711 then
712 Error_Msg_N
713 ("protected function cannot modify protected object",
714 Lhs);
715 end if;
717 -- Changes of the ceiling priority of the protected object
718 -- are only effective if the Ceiling_Locking policy is in
719 -- effect (AARM D.5.2 (5/2)).
721 if Locking_Policy /= 'C' then
722 Error_Msg_N
723 ("assignment to the attribute PRIORITY has no effect??",
724 Lhs);
725 Error_Msg_N
726 ("\since no Locking_Policy has been specified??", Lhs);
727 end if;
729 goto Leave;
730 end if;
731 end if;
732 end;
734 Diagnose_Non_Variable_Lhs (Lhs);
735 goto Leave;
737 -- Error of assigning to limited type. We do however allow this in
738 -- certain cases where the front end generates the assignments.
740 elsif Is_Limited_Type (T1)
741 and then not Assignment_OK (Lhs)
742 and then not Assignment_OK (Original_Node (Lhs))
743 then
744 -- CPP constructors can only be called in declarations
746 if Is_CPP_Constructor_Call (Rhs) then
747 Error_Msg_N ("invalid use of 'C'P'P constructor", Rhs);
748 else
749 Error_Msg_N
750 ("left hand of assignment must not be limited type", Lhs);
751 Explain_Limited_Type (T1, Lhs);
752 end if;
754 goto Leave;
756 -- A class-wide type may be a limited view. This illegal case is not
757 -- caught by previous checks.
759 elsif Ekind (T1) = E_Class_Wide_Type and then From_Limited_With (T1) then
760 Error_Msg_NE ("invalid use of limited view of&", Lhs, T1);
761 goto Leave;
763 -- Enforce RM 3.9.3 (8): the target of an assignment operation cannot be
764 -- abstract. This is only checked when the assignment Comes_From_Source,
765 -- because in some cases the expander generates such assignments (such
766 -- in the _assign operation for an abstract type).
768 elsif Is_Abstract_Type (T1) and then Comes_From_Source (N) then
769 Error_Msg_N
770 ("target of assignment operation must not be abstract", Lhs);
771 end if;
773 -- Variables which are Part_Of constituents of single protected types
774 -- behave in similar fashion to protected components. Such variables
775 -- cannot be modified by protected functions.
777 if Is_Protected_Part_Of_Constituent (Lhs) and then Within_Function then
778 Error_Msg_N
779 ("protected function cannot modify protected object", Lhs);
780 end if;
782 -- Resolution may have updated the subtype, in case the left-hand side
783 -- is a private protected component. Use the correct subtype to avoid
784 -- scoping issues in the back-end.
786 T1 := Etype (Lhs);
788 -- Ada 2005 (AI-50217, AI-326): Check wrong dereference of incomplete
789 -- type. For example:
791 -- limited with P;
792 -- package Pkg is
793 -- type Acc is access P.T;
794 -- end Pkg;
796 -- with Pkg; use Acc;
797 -- procedure Example is
798 -- A, B : Acc;
799 -- begin
800 -- A.all := B.all; -- ERROR
801 -- end Example;
803 if Nkind (Lhs) = N_Explicit_Dereference
804 and then Ekind (T1) = E_Incomplete_Type
805 then
806 Error_Msg_N ("invalid use of incomplete type", Lhs);
807 Kill_Lhs;
808 goto Leave;
809 end if;
811 -- Now we can complete the resolution of the right hand side
813 Set_Assignment_Type (Lhs, T1);
815 -- If the target of the assignment is an entity of a mutable type and
816 -- the expression is a conditional expression, its alternatives can be
817 -- of different subtypes of the nominal type of the LHS, so they must be
818 -- resolved with the base type, given that their subtype may differ from
819 -- that of the target mutable object.
821 if Is_Entity_Name (Lhs)
822 and then Ekind_In (Entity (Lhs), E_In_Out_Parameter,
823 E_Out_Parameter,
824 E_Variable)
825 and then Is_Composite_Type (T1)
826 and then not Is_Constrained (Etype (Entity (Lhs)))
827 and then Nkind_In (Rhs, N_If_Expression, N_Case_Expression)
828 then
829 Resolve (Rhs, Base_Type (T1));
831 else
832 Resolve (Rhs, T1);
833 end if;
835 -- This is the point at which we check for an unset reference
837 Check_Unset_Reference (Rhs);
838 Check_Unprotected_Access (Lhs, Rhs);
840 -- Remaining steps are skipped if Rhs was syntactically in error
842 if Rhs = Error then
843 Kill_Lhs;
844 goto Leave;
845 end if;
847 T2 := Etype (Rhs);
849 if not Covers (T1, T2) then
850 Wrong_Type (Rhs, Etype (Lhs));
851 Kill_Lhs;
852 goto Leave;
853 end if;
855 -- Ada 2005 (AI-326): In case of explicit dereference of incomplete
856 -- types, use the non-limited view if available
858 if Nkind (Rhs) = N_Explicit_Dereference
859 and then Is_Tagged_Type (T2)
860 and then Has_Non_Limited_View (T2)
861 then
862 T2 := Non_Limited_View (T2);
863 end if;
865 Set_Assignment_Type (Rhs, T2);
867 if Total_Errors_Detected /= 0 then
868 if No (T1) then
869 T1 := Any_Type;
870 end if;
872 if No (T2) then
873 T2 := Any_Type;
874 end if;
875 end if;
877 if T1 = Any_Type or else T2 = Any_Type then
878 Kill_Lhs;
879 goto Leave;
880 end if;
882 -- If the rhs is class-wide or dynamically tagged, then require the lhs
883 -- to be class-wide. The case where the rhs is a dynamically tagged call
884 -- to a dispatching operation with a controlling access result is
885 -- excluded from this check, since the target has an access type (and
886 -- no tag propagation occurs in that case).
888 if (Is_Class_Wide_Type (T2)
889 or else (Is_Dynamically_Tagged (Rhs)
890 and then not Is_Access_Type (T1)))
891 and then not Is_Class_Wide_Type (T1)
892 then
893 Error_Msg_N ("dynamically tagged expression not allowed!", Rhs);
895 elsif Is_Class_Wide_Type (T1)
896 and then not Is_Class_Wide_Type (T2)
897 and then not Is_Tag_Indeterminate (Rhs)
898 and then not Is_Dynamically_Tagged (Rhs)
899 then
900 Error_Msg_N ("dynamically tagged expression required!", Rhs);
901 end if;
903 -- Propagate the tag from a class-wide target to the rhs when the rhs
904 -- is a tag-indeterminate call.
906 if Is_Tag_Indeterminate (Rhs) then
907 if Is_Class_Wide_Type (T1) then
908 Propagate_Tag (Lhs, Rhs);
910 elsif Nkind (Rhs) = N_Function_Call
911 and then Is_Entity_Name (Name (Rhs))
912 and then Is_Abstract_Subprogram (Entity (Name (Rhs)))
913 then
914 Error_Msg_N
915 ("call to abstract function must be dispatching", Name (Rhs));
917 elsif Nkind (Rhs) = N_Qualified_Expression
918 and then Nkind (Expression (Rhs)) = N_Function_Call
919 and then Is_Entity_Name (Name (Expression (Rhs)))
920 and then
921 Is_Abstract_Subprogram (Entity (Name (Expression (Rhs))))
922 then
923 Error_Msg_N
924 ("call to abstract function must be dispatching",
925 Name (Expression (Rhs)));
926 end if;
927 end if;
929 -- Ada 2005 (AI-385): When the lhs type is an anonymous access type,
930 -- apply an implicit conversion of the rhs to that type to force
931 -- appropriate static and run-time accessibility checks. This applies
932 -- as well to anonymous access-to-subprogram types that are component
933 -- subtypes or formal parameters.
935 if Ada_Version >= Ada_2005 and then Is_Access_Type (T1) then
936 if Is_Local_Anonymous_Access (T1)
937 or else Ekind (T2) = E_Anonymous_Access_Subprogram_Type
939 -- Handle assignment to an Ada 2012 stand-alone object
940 -- of an anonymous access type.
942 or else (Ekind (T1) = E_Anonymous_Access_Type
943 and then Nkind (Associated_Node_For_Itype (T1)) =
944 N_Object_Declaration)
946 then
947 Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
948 Analyze_And_Resolve (Rhs, T1);
949 end if;
950 end if;
952 -- Ada 2005 (AI-231): Assignment to not null variable
954 if Ada_Version >= Ada_2005
955 and then Can_Never_Be_Null (T1)
956 and then not Assignment_OK (Lhs)
957 then
958 -- Case where we know the right hand side is null
960 if Known_Null (Rhs) then
961 Apply_Compile_Time_Constraint_Error
962 (N => Rhs,
963 Msg =>
964 "(Ada 2005) null not allowed in null-excluding objects??",
965 Reason => CE_Null_Not_Allowed);
967 -- We still mark this as a possible modification, that's necessary
968 -- to reset Is_True_Constant, and desirable for xref purposes.
970 Note_Possible_Modification (Lhs, Sure => True);
971 goto Leave;
973 -- If we know the right hand side is non-null, then we convert to the
974 -- target type, since we don't need a run time check in that case.
976 elsif not Can_Never_Be_Null (T2) then
977 Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
978 Analyze_And_Resolve (Rhs, T1);
979 end if;
980 end if;
982 if Is_Scalar_Type (T1) then
983 Apply_Scalar_Range_Check (Rhs, Etype (Lhs));
985 -- For array types, verify that lengths match. If the right hand side
986 -- is a function call that has been inlined, the assignment has been
987 -- rewritten as a block, and the constraint check will be applied to the
988 -- assignment within the block.
990 elsif Is_Array_Type (T1)
991 and then (Nkind (Rhs) /= N_Type_Conversion
992 or else Is_Constrained (Etype (Rhs)))
993 and then (Nkind (Rhs) /= N_Function_Call
994 or else Nkind (N) /= N_Block_Statement)
995 then
996 -- Assignment verifies that the length of the Lsh and Rhs are equal,
997 -- but of course the indexes do not have to match. If the right-hand
998 -- side is a type conversion to an unconstrained type, a length check
999 -- is performed on the expression itself during expansion. In rare
1000 -- cases, the redundant length check is computed on an index type
1001 -- with a different representation, triggering incorrect code in the
1002 -- back end.
1004 Apply_Length_Check (Rhs, Etype (Lhs));
1006 else
1007 -- Discriminant checks are applied in the course of expansion
1009 null;
1010 end if;
1012 -- Note: modifications of the Lhs may only be recorded after
1013 -- checks have been applied.
1015 Note_Possible_Modification (Lhs, Sure => True);
1017 -- ??? a real accessibility check is needed when ???
1019 -- Post warning for redundant assignment or variable to itself
1021 if Warn_On_Redundant_Constructs
1023 -- We only warn for source constructs
1025 and then Comes_From_Source (N)
1027 -- Where the object is the same on both sides
1029 and then Same_Object (Lhs, Original_Node (Rhs))
1031 -- But exclude the case where the right side was an operation that
1032 -- got rewritten (e.g. JUNK + K, where K was known to be zero). We
1033 -- don't want to warn in such a case, since it is reasonable to write
1034 -- such expressions especially when K is defined symbolically in some
1035 -- other package.
1037 and then Nkind (Original_Node (Rhs)) not in N_Op
1038 then
1039 if Nkind (Lhs) in N_Has_Entity then
1040 Error_Msg_NE -- CODEFIX
1041 ("?r?useless assignment of & to itself!", N, Entity (Lhs));
1042 else
1043 Error_Msg_N -- CODEFIX
1044 ("?r?useless assignment of object to itself!", N);
1045 end if;
1046 end if;
1048 -- Check for non-allowed composite assignment
1050 if not Support_Composite_Assign_On_Target
1051 and then (Is_Array_Type (T1) or else Is_Record_Type (T1))
1052 and then (not Has_Size_Clause (T1) or else Esize (T1) > 64)
1053 then
1054 Error_Msg_CRT ("composite assignment", N);
1055 end if;
1057 -- Check elaboration warning for left side if not in elab code
1059 if Legacy_Elaboration_Checks
1060 and not In_Subprogram_Or_Concurrent_Unit
1061 then
1062 Check_Elab_Assign (Lhs);
1063 end if;
1065 -- Save the scenario for later examination by the ABE Processing phase
1067 Record_Elaboration_Scenario (N);
1069 -- Set Referenced_As_LHS if appropriate. We only set this flag if the
1070 -- assignment is a source assignment in the extended main source unit.
1071 -- We are not interested in any reference information outside this
1072 -- context, or in compiler generated assignment statements.
1074 if Comes_From_Source (N)
1075 and then In_Extended_Main_Source_Unit (Lhs)
1076 then
1077 Set_Referenced_Modified (Lhs, Out_Param => False);
1078 end if;
1080 -- RM 7.3.2 (12/3): An assignment to a view conversion (from a type to
1081 -- one of its ancestors) requires an invariant check. Apply check only
1082 -- if expression comes from source, otherwise it will be applied when
1083 -- value is assigned to source entity. This is not done in GNATprove
1084 -- mode, as GNATprove handles invariant checks itself.
1086 if Nkind (Lhs) = N_Type_Conversion
1087 and then Has_Invariants (Etype (Expression (Lhs)))
1088 and then Comes_From_Source (Expression (Lhs))
1089 and then not GNATprove_Mode
1090 then
1091 Insert_After (N, Make_Invariant_Call (Expression (Lhs)));
1092 end if;
1094 -- Final step. If left side is an entity, then we may be able to reset
1095 -- the current tracked values to new safe values. We only have something
1096 -- to do if the left side is an entity name, and expansion has not
1097 -- modified the node into something other than an assignment, and of
1098 -- course we only capture values if it is safe to do so.
1100 if Is_Entity_Name (Lhs)
1101 and then Nkind (N) = N_Assignment_Statement
1102 then
1103 declare
1104 Ent : constant Entity_Id := Entity (Lhs);
1106 begin
1107 if Safe_To_Capture_Value (N, Ent) then
1109 -- If simple variable on left side, warn if this assignment
1110 -- blots out another one (rendering it useless). We only do
1111 -- this for source assignments, otherwise we can generate bogus
1112 -- warnings when an assignment is rewritten as another
1113 -- assignment, and gets tied up with itself.
1115 -- There may have been a previous reference to a component of
1116 -- the variable, which in general removes the Last_Assignment
1117 -- field of the variable to indicate a relevant use of the
1118 -- previous assignment. However, if the assignment is to a
1119 -- subcomponent the reference may not have registered, because
1120 -- it is not possible to determine whether the context is an
1121 -- assignment. In those cases we generate a Deferred_Reference,
1122 -- to be used at the end of compilation to generate the right
1123 -- kind of reference, and we suppress a potential warning for
1124 -- a useless assignment, which might be premature. This may
1125 -- lose a warning in rare cases, but seems preferable to a
1126 -- misleading warning.
1128 if Warn_On_Modified_Unread
1129 and then Is_Assignable (Ent)
1130 and then Comes_From_Source (N)
1131 and then In_Extended_Main_Source_Unit (Ent)
1132 and then not Has_Deferred_Reference (Ent)
1133 then
1134 Warn_On_Useless_Assignment (Ent, N);
1135 end if;
1137 -- If we are assigning an access type and the left side is an
1138 -- entity, then make sure that the Is_Known_[Non_]Null flags
1139 -- properly reflect the state of the entity after assignment.
1141 if Is_Access_Type (T1) then
1142 if Known_Non_Null (Rhs) then
1143 Set_Is_Known_Non_Null (Ent, True);
1145 elsif Known_Null (Rhs)
1146 and then not Can_Never_Be_Null (Ent)
1147 then
1148 Set_Is_Known_Null (Ent, True);
1150 else
1151 Set_Is_Known_Null (Ent, False);
1153 if not Can_Never_Be_Null (Ent) then
1154 Set_Is_Known_Non_Null (Ent, False);
1155 end if;
1156 end if;
1158 -- For discrete types, we may be able to set the current value
1159 -- if the value is known at compile time.
1161 elsif Is_Discrete_Type (T1)
1162 and then Compile_Time_Known_Value (Rhs)
1163 then
1164 Set_Current_Value (Ent, Rhs);
1165 else
1166 Set_Current_Value (Ent, Empty);
1167 end if;
1169 -- If not safe to capture values, kill them
1171 else
1172 Kill_Lhs;
1173 end if;
1174 end;
1175 end if;
1177 -- If assigning to an object in whole or in part, note location of
1178 -- assignment in case no one references value. We only do this for
1179 -- source assignments, otherwise we can generate bogus warnings when an
1180 -- assignment is rewritten as another assignment, and gets tied up with
1181 -- itself.
1183 declare
1184 Ent : constant Entity_Id := Get_Enclosing_Object (Lhs);
1185 begin
1186 if Present (Ent)
1187 and then Safe_To_Capture_Value (N, Ent)
1188 and then Nkind (N) = N_Assignment_Statement
1189 and then Warn_On_Modified_Unread
1190 and then Is_Assignable (Ent)
1191 and then Comes_From_Source (N)
1192 and then In_Extended_Main_Source_Unit (Ent)
1193 then
1194 Set_Last_Assignment (Ent, Lhs);
1195 end if;
1196 end;
1198 Analyze_Dimension (N);
1200 <<Leave>>
1201 Restore_Ghost_Region (Saved_GM, Saved_IGR);
1203 -- If the right-hand side contains target names, expansion has been
1204 -- disabled to prevent expansion that might move target names out of
1205 -- the context of the assignment statement. Restore the expander mode
1206 -- now so that assignment statement can be properly expanded.
1208 if Nkind (N) = N_Assignment_Statement then
1209 if Has_Target_Names (N) then
1210 Expander_Mode_Restore;
1211 Full_Analysis := Save_Full_Analysis;
1212 end if;
1214 pragma Assert (not Should_Transform_BIP_Assignment (Typ => T1));
1215 end if;
1216 end Analyze_Assignment;
1218 -----------------------------
1219 -- Analyze_Block_Statement --
1220 -----------------------------
1222 procedure Analyze_Block_Statement (N : Node_Id) is
1223 procedure Install_Return_Entities (Scop : Entity_Id);
1224 -- Install all entities of return statement scope Scop in the visibility
1225 -- chain except for the return object since its entity is reused in a
1226 -- renaming.
1228 -----------------------------
1229 -- Install_Return_Entities --
1230 -----------------------------
1232 procedure Install_Return_Entities (Scop : Entity_Id) is
1233 Id : Entity_Id;
1235 begin
1236 Id := First_Entity (Scop);
1237 while Present (Id) loop
1239 -- Do not install the return object
1241 if not Ekind_In (Id, E_Constant, E_Variable)
1242 or else not Is_Return_Object (Id)
1243 then
1244 Install_Entity (Id);
1245 end if;
1247 Next_Entity (Id);
1248 end loop;
1249 end Install_Return_Entities;
1251 -- Local constants and variables
1253 Decls : constant List_Id := Declarations (N);
1254 Id : constant Node_Id := Identifier (N);
1255 HSS : constant Node_Id := Handled_Statement_Sequence (N);
1257 Is_BIP_Return_Statement : Boolean;
1259 -- Start of processing for Analyze_Block_Statement
1261 begin
1262 -- In SPARK mode, we reject block statements. Note that the case of
1263 -- block statements generated by the expander is fine.
1265 if Nkind (Original_Node (N)) = N_Block_Statement then
1266 Check_SPARK_05_Restriction ("block statement is not allowed", N);
1267 end if;
1269 -- If no handled statement sequence is present, things are really messed
1270 -- up, and we just return immediately (defence against previous errors).
1272 if No (HSS) then
1273 Check_Error_Detected;
1274 return;
1275 end if;
1277 -- Detect whether the block is actually a rewritten return statement of
1278 -- a build-in-place function.
1280 Is_BIP_Return_Statement :=
1281 Present (Id)
1282 and then Present (Entity (Id))
1283 and then Ekind (Entity (Id)) = E_Return_Statement
1284 and then Is_Build_In_Place_Function
1285 (Return_Applies_To (Entity (Id)));
1287 -- Normal processing with HSS present
1289 declare
1290 EH : constant List_Id := Exception_Handlers (HSS);
1291 Ent : Entity_Id := Empty;
1292 S : Entity_Id;
1294 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1295 -- Recursively save value of this global, will be restored on exit
1297 begin
1298 -- Initialize unblocked exit count for statements of begin block
1299 -- plus one for each exception handler that is present.
1301 Unblocked_Exit_Count := 1;
1303 if Present (EH) then
1304 Unblocked_Exit_Count := Unblocked_Exit_Count + List_Length (EH);
1305 end if;
1307 -- If a label is present analyze it and mark it as referenced
1309 if Present (Id) then
1310 Analyze (Id);
1311 Ent := Entity (Id);
1313 -- An error defense. If we have an identifier, but no entity, then
1314 -- something is wrong. If previous errors, then just remove the
1315 -- identifier and continue, otherwise raise an exception.
1317 if No (Ent) then
1318 Check_Error_Detected;
1319 Set_Identifier (N, Empty);
1321 else
1322 Set_Ekind (Ent, E_Block);
1323 Generate_Reference (Ent, N, ' ');
1324 Generate_Definition (Ent);
1326 if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
1327 Set_Label_Construct (Parent (Ent), N);
1328 end if;
1329 end if;
1330 end if;
1332 -- If no entity set, create a label entity
1334 if No (Ent) then
1335 Ent := New_Internal_Entity (E_Block, Current_Scope, Sloc (N), 'B');
1336 Set_Identifier (N, New_Occurrence_Of (Ent, Sloc (N)));
1337 Set_Parent (Ent, N);
1338 end if;
1340 Set_Etype (Ent, Standard_Void_Type);
1341 Set_Block_Node (Ent, Identifier (N));
1342 Push_Scope (Ent);
1344 -- The block served as an extended return statement. Ensure that any
1345 -- entities created during the analysis and expansion of the return
1346 -- object declaration are once again visible.
1348 if Is_BIP_Return_Statement then
1349 Install_Return_Entities (Ent);
1350 end if;
1352 if Present (Decls) then
1353 Analyze_Declarations (Decls);
1354 Check_Completion;
1355 Inspect_Deferred_Constant_Completion (Decls);
1356 end if;
1358 Analyze (HSS);
1359 Process_End_Label (HSS, 'e', Ent);
1361 -- If exception handlers are present, then we indicate that enclosing
1362 -- scopes contain a block with handlers. We only need to mark non-
1363 -- generic scopes.
1365 if Present (EH) then
1366 S := Scope (Ent);
1367 loop
1368 Set_Has_Nested_Block_With_Handler (S);
1369 exit when Is_Overloadable (S)
1370 or else Ekind (S) = E_Package
1371 or else Is_Generic_Unit (S);
1372 S := Scope (S);
1373 end loop;
1374 end if;
1376 Check_References (Ent);
1377 Update_Use_Clause_Chain;
1378 End_Scope;
1380 if Unblocked_Exit_Count = 0 then
1381 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1382 Check_Unreachable_Code (N);
1383 else
1384 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1385 end if;
1386 end;
1387 end Analyze_Block_Statement;
1389 --------------------------------
1390 -- Analyze_Compound_Statement --
1391 --------------------------------
1393 procedure Analyze_Compound_Statement (N : Node_Id) is
1394 begin
1395 Analyze_List (Actions (N));
1396 end Analyze_Compound_Statement;
1398 ----------------------------
1399 -- Analyze_Case_Statement --
1400 ----------------------------
1402 procedure Analyze_Case_Statement (N : Node_Id) is
1403 Exp : Node_Id;
1404 Exp_Type : Entity_Id;
1405 Exp_Btype : Entity_Id;
1406 Last_Choice : Nat;
1408 Others_Present : Boolean;
1409 -- Indicates if Others was present
1411 pragma Warnings (Off, Last_Choice);
1412 -- Don't care about assigned value
1414 Statements_Analyzed : Boolean := False;
1415 -- Set True if at least some statement sequences get analyzed. If False
1416 -- on exit, means we had a serious error that prevented full analysis of
1417 -- the case statement, and as a result it is not a good idea to output
1418 -- warning messages about unreachable code.
1420 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1421 -- Recursively save value of this global, will be restored on exit
1423 procedure Non_Static_Choice_Error (Choice : Node_Id);
1424 -- Error routine invoked by the generic instantiation below when the
1425 -- case statement has a non static choice.
1427 procedure Process_Statements (Alternative : Node_Id);
1428 -- Analyzes the statements associated with a case alternative. Needed
1429 -- by instantiation below.
1431 package Analyze_Case_Choices is new
1432 Generic_Analyze_Choices
1433 (Process_Associated_Node => Process_Statements);
1434 use Analyze_Case_Choices;
1435 -- Instantiation of the generic choice analysis package
1437 package Check_Case_Choices is new
1438 Generic_Check_Choices
1439 (Process_Empty_Choice => No_OP,
1440 Process_Non_Static_Choice => Non_Static_Choice_Error,
1441 Process_Associated_Node => No_OP);
1442 use Check_Case_Choices;
1443 -- Instantiation of the generic choice processing package
1445 -----------------------------
1446 -- Non_Static_Choice_Error --
1447 -----------------------------
1449 procedure Non_Static_Choice_Error (Choice : Node_Id) is
1450 begin
1451 Flag_Non_Static_Expr
1452 ("choice given in case statement is not static!", Choice);
1453 end Non_Static_Choice_Error;
1455 ------------------------
1456 -- Process_Statements --
1457 ------------------------
1459 procedure Process_Statements (Alternative : Node_Id) is
1460 Choices : constant List_Id := Discrete_Choices (Alternative);
1461 Ent : Entity_Id;
1463 begin
1464 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1465 Statements_Analyzed := True;
1467 -- An interesting optimization. If the case statement expression
1468 -- is a simple entity, then we can set the current value within an
1469 -- alternative if the alternative has one possible value.
1471 -- case N is
1472 -- when 1 => alpha
1473 -- when 2 | 3 => beta
1474 -- when others => gamma
1476 -- Here we know that N is initially 1 within alpha, but for beta and
1477 -- gamma, we do not know anything more about the initial value.
1479 if Is_Entity_Name (Exp) then
1480 Ent := Entity (Exp);
1482 if Ekind_In (Ent, E_Variable,
1483 E_In_Out_Parameter,
1484 E_Out_Parameter)
1485 then
1486 if List_Length (Choices) = 1
1487 and then Nkind (First (Choices)) in N_Subexpr
1488 and then Compile_Time_Known_Value (First (Choices))
1489 then
1490 Set_Current_Value (Entity (Exp), First (Choices));
1491 end if;
1493 Analyze_Statements (Statements (Alternative));
1495 -- After analyzing the case, set the current value to empty
1496 -- since we won't know what it is for the next alternative
1497 -- (unless reset by this same circuit), or after the case.
1499 Set_Current_Value (Entity (Exp), Empty);
1500 return;
1501 end if;
1502 end if;
1504 -- Case where expression is not an entity name of a variable
1506 Analyze_Statements (Statements (Alternative));
1507 end Process_Statements;
1509 -- Start of processing for Analyze_Case_Statement
1511 begin
1512 Unblocked_Exit_Count := 0;
1513 Exp := Expression (N);
1514 Analyze (Exp);
1516 -- The expression must be of any discrete type. In rare cases, the
1517 -- expander constructs a case statement whose expression has a private
1518 -- type whose full view is discrete. This can happen when generating
1519 -- a stream operation for a variant type after the type is frozen,
1520 -- when the partial of view of the type of the discriminant is private.
1521 -- In that case, use the full view to analyze case alternatives.
1523 if not Is_Overloaded (Exp)
1524 and then not Comes_From_Source (N)
1525 and then Is_Private_Type (Etype (Exp))
1526 and then Present (Full_View (Etype (Exp)))
1527 and then Is_Discrete_Type (Full_View (Etype (Exp)))
1528 then
1529 Resolve (Exp, Etype (Exp));
1530 Exp_Type := Full_View (Etype (Exp));
1532 else
1533 Analyze_And_Resolve (Exp, Any_Discrete);
1534 Exp_Type := Etype (Exp);
1535 end if;
1537 Check_Unset_Reference (Exp);
1538 Exp_Btype := Base_Type (Exp_Type);
1540 -- The expression must be of a discrete type which must be determinable
1541 -- independently of the context in which the expression occurs, but
1542 -- using the fact that the expression must be of a discrete type.
1543 -- Moreover, the type this expression must not be a character literal
1544 -- (which is always ambiguous) or, for Ada-83, a generic formal type.
1546 -- If error already reported by Resolve, nothing more to do
1548 if Exp_Btype = Any_Discrete or else Exp_Btype = Any_Type then
1549 return;
1551 elsif Exp_Btype = Any_Character then
1552 Error_Msg_N
1553 ("character literal as case expression is ambiguous", Exp);
1554 return;
1556 elsif Ada_Version = Ada_83
1557 and then (Is_Generic_Type (Exp_Btype)
1558 or else Is_Generic_Type (Root_Type (Exp_Btype)))
1559 then
1560 Error_Msg_N
1561 ("(Ada 83) case expression cannot be of a generic type", Exp);
1562 return;
1563 end if;
1565 -- If the case expression is a formal object of mode in out, then treat
1566 -- it as having a nonstatic subtype by forcing use of the base type
1567 -- (which has to get passed to Check_Case_Choices below). Also use base
1568 -- type when the case expression is parenthesized.
1570 if Paren_Count (Exp) > 0
1571 or else (Is_Entity_Name (Exp)
1572 and then Ekind (Entity (Exp)) = E_Generic_In_Out_Parameter)
1573 then
1574 Exp_Type := Exp_Btype;
1575 end if;
1577 -- Call instantiated procedures to analyzwe and check discrete choices
1579 Analyze_Choices (Alternatives (N), Exp_Type);
1580 Check_Choices (N, Alternatives (N), Exp_Type, Others_Present);
1582 -- Case statement with single OTHERS alternative not allowed in SPARK
1584 if Others_Present and then List_Length (Alternatives (N)) = 1 then
1585 Check_SPARK_05_Restriction
1586 ("OTHERS as unique case alternative is not allowed", N);
1587 end if;
1589 if Exp_Type = Universal_Integer and then not Others_Present then
1590 Error_Msg_N ("case on universal integer requires OTHERS choice", Exp);
1591 end if;
1593 -- If all our exits were blocked by unconditional transfers of control,
1594 -- then the entire CASE statement acts as an unconditional transfer of
1595 -- control, so treat it like one, and check unreachable code. Skip this
1596 -- test if we had serious errors preventing any statement analysis.
1598 if Unblocked_Exit_Count = 0 and then Statements_Analyzed then
1599 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1600 Check_Unreachable_Code (N);
1601 else
1602 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1603 end if;
1605 -- If the expander is active it will detect the case of a statically
1606 -- determined single alternative and remove warnings for the case, but
1607 -- if we are not doing expansion, that circuit won't be active. Here we
1608 -- duplicate the effect of removing warnings in the same way, so that
1609 -- we will get the same set of warnings in -gnatc mode.
1611 if not Expander_Active
1612 and then Compile_Time_Known_Value (Expression (N))
1613 and then Serious_Errors_Detected = 0
1614 then
1615 declare
1616 Chosen : constant Node_Id := Find_Static_Alternative (N);
1617 Alt : Node_Id;
1619 begin
1620 Alt := First (Alternatives (N));
1621 while Present (Alt) loop
1622 if Alt /= Chosen then
1623 Remove_Warning_Messages (Statements (Alt));
1624 end if;
1626 Next (Alt);
1627 end loop;
1628 end;
1629 end if;
1630 end Analyze_Case_Statement;
1632 ----------------------------
1633 -- Analyze_Exit_Statement --
1634 ----------------------------
1636 -- If the exit includes a name, it must be the name of a currently open
1637 -- loop. Otherwise there must be an innermost open loop on the stack, to
1638 -- which the statement implicitly refers.
1640 -- Additionally, in SPARK mode:
1642 -- The exit can only name the closest enclosing loop;
1644 -- An exit with a when clause must be directly contained in a loop;
1646 -- An exit without a when clause must be directly contained in an
1647 -- if-statement with no elsif or else, which is itself directly contained
1648 -- in a loop. The exit must be the last statement in the if-statement.
1650 procedure Analyze_Exit_Statement (N : Node_Id) is
1651 Target : constant Node_Id := Name (N);
1652 Cond : constant Node_Id := Condition (N);
1653 Scope_Id : Entity_Id := Empty; -- initialize to prevent warning
1654 U_Name : Entity_Id;
1655 Kind : Entity_Kind;
1657 begin
1658 if No (Cond) then
1659 Check_Unreachable_Code (N);
1660 end if;
1662 if Present (Target) then
1663 Analyze (Target);
1664 U_Name := Entity (Target);
1666 if not In_Open_Scopes (U_Name) or else Ekind (U_Name) /= E_Loop then
1667 Error_Msg_N ("invalid loop name in exit statement", N);
1668 return;
1670 else
1671 if Has_Loop_In_Inner_Open_Scopes (U_Name) then
1672 Check_SPARK_05_Restriction
1673 ("exit label must name the closest enclosing loop", N);
1674 end if;
1676 Set_Has_Exit (U_Name);
1677 end if;
1679 else
1680 U_Name := Empty;
1681 end if;
1683 for J in reverse 0 .. Scope_Stack.Last loop
1684 Scope_Id := Scope_Stack.Table (J).Entity;
1685 Kind := Ekind (Scope_Id);
1687 if Kind = E_Loop and then (No (Target) or else Scope_Id = U_Name) then
1688 Set_Has_Exit (Scope_Id);
1689 exit;
1691 elsif Kind = E_Block
1692 or else Kind = E_Loop
1693 or else Kind = E_Return_Statement
1694 then
1695 null;
1697 else
1698 Error_Msg_N
1699 ("cannot exit from program unit or accept statement", N);
1700 return;
1701 end if;
1702 end loop;
1704 -- Verify that if present the condition is a Boolean expression
1706 if Present (Cond) then
1707 Analyze_And_Resolve (Cond, Any_Boolean);
1708 Check_Unset_Reference (Cond);
1709 end if;
1711 -- In SPARK mode, verify that the exit statement respects the SPARK
1712 -- restrictions.
1714 if Present (Cond) then
1715 if Nkind (Parent (N)) /= N_Loop_Statement then
1716 Check_SPARK_05_Restriction
1717 ("exit with when clause must be directly in loop", N);
1718 end if;
1720 else
1721 if Nkind (Parent (N)) /= N_If_Statement then
1722 if Nkind (Parent (N)) = N_Elsif_Part then
1723 Check_SPARK_05_Restriction
1724 ("exit must be in IF without ELSIF", N);
1725 else
1726 Check_SPARK_05_Restriction ("exit must be directly in IF", N);
1727 end if;
1729 elsif Nkind (Parent (Parent (N))) /= N_Loop_Statement then
1730 Check_SPARK_05_Restriction
1731 ("exit must be in IF directly in loop", N);
1733 -- First test the presence of ELSE, so that an exit in an ELSE leads
1734 -- to an error mentioning the ELSE.
1736 elsif Present (Else_Statements (Parent (N))) then
1737 Check_SPARK_05_Restriction ("exit must be in IF without ELSE", N);
1739 -- An exit in an ELSIF does not reach here, as it would have been
1740 -- detected in the case (Nkind (Parent (N)) /= N_If_Statement).
1742 elsif Present (Elsif_Parts (Parent (N))) then
1743 Check_SPARK_05_Restriction ("exit must be in IF without ELSIF", N);
1744 end if;
1745 end if;
1747 -- Chain exit statement to associated loop entity
1749 Set_Next_Exit_Statement (N, First_Exit_Statement (Scope_Id));
1750 Set_First_Exit_Statement (Scope_Id, N);
1752 -- Since the exit may take us out of a loop, any previous assignment
1753 -- statement is not useless, so clear last assignment indications. It
1754 -- is OK to keep other current values, since if the exit statement
1755 -- does not exit, then the current values are still valid.
1757 Kill_Current_Values (Last_Assignment_Only => True);
1758 end Analyze_Exit_Statement;
1760 ----------------------------
1761 -- Analyze_Goto_Statement --
1762 ----------------------------
1764 procedure Analyze_Goto_Statement (N : Node_Id) is
1765 Label : constant Node_Id := Name (N);
1766 Scope_Id : Entity_Id;
1767 Label_Scope : Entity_Id;
1768 Label_Ent : Entity_Id;
1770 begin
1771 Check_SPARK_05_Restriction ("goto statement is not allowed", N);
1773 -- Actual semantic checks
1775 Check_Unreachable_Code (N);
1776 Kill_Current_Values (Last_Assignment_Only => True);
1778 Analyze (Label);
1779 Label_Ent := Entity (Label);
1781 -- Ignore previous error
1783 if Label_Ent = Any_Id then
1784 Check_Error_Detected;
1785 return;
1787 -- We just have a label as the target of a goto
1789 elsif Ekind (Label_Ent) /= E_Label then
1790 Error_Msg_N ("target of goto statement must be a label", Label);
1791 return;
1793 -- Check that the target of the goto is reachable according to Ada
1794 -- scoping rules. Note: the special gotos we generate for optimizing
1795 -- local handling of exceptions would violate these rules, but we mark
1796 -- such gotos as analyzed when built, so this code is never entered.
1798 elsif not Reachable (Label_Ent) then
1799 Error_Msg_N ("target of goto statement is not reachable", Label);
1800 return;
1801 end if;
1803 -- Here if goto passes initial validity checks
1805 Label_Scope := Enclosing_Scope (Label_Ent);
1807 for J in reverse 0 .. Scope_Stack.Last loop
1808 Scope_Id := Scope_Stack.Table (J).Entity;
1810 if Label_Scope = Scope_Id
1811 or else not Ekind_In (Scope_Id, E_Block, E_Loop, E_Return_Statement)
1812 then
1813 if Scope_Id /= Label_Scope then
1814 Error_Msg_N
1815 ("cannot exit from program unit or accept statement", N);
1816 end if;
1818 return;
1819 end if;
1820 end loop;
1822 raise Program_Error;
1823 end Analyze_Goto_Statement;
1825 --------------------------
1826 -- Analyze_If_Statement --
1827 --------------------------
1829 -- A special complication arises in the analysis of if statements
1831 -- The expander has circuitry to completely delete code that it can tell
1832 -- will not be executed (as a result of compile time known conditions). In
1833 -- the analyzer, we ensure that code that will be deleted in this manner
1834 -- is analyzed but not expanded. This is obviously more efficient, but
1835 -- more significantly, difficulties arise if code is expanded and then
1836 -- eliminated (e.g. exception table entries disappear). Similarly, itypes
1837 -- generated in deleted code must be frozen from start, because the nodes
1838 -- on which they depend will not be available at the freeze point.
1840 procedure Analyze_If_Statement (N : Node_Id) is
1841 E : Node_Id;
1843 Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1844 -- Recursively save value of this global, will be restored on exit
1846 Save_In_Deleted_Code : Boolean;
1848 Del : Boolean := False;
1849 -- This flag gets set True if a True condition has been found, which
1850 -- means that remaining ELSE/ELSIF parts are deleted.
1852 procedure Analyze_Cond_Then (Cnode : Node_Id);
1853 -- This is applied to either the N_If_Statement node itself or to an
1854 -- N_Elsif_Part node. It deals with analyzing the condition and the THEN
1855 -- statements associated with it.
1857 -----------------------
1858 -- Analyze_Cond_Then --
1859 -----------------------
1861 procedure Analyze_Cond_Then (Cnode : Node_Id) is
1862 Cond : constant Node_Id := Condition (Cnode);
1863 Tstm : constant List_Id := Then_Statements (Cnode);
1865 begin
1866 Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1867 Analyze_And_Resolve (Cond, Any_Boolean);
1868 Check_Unset_Reference (Cond);
1869 Set_Current_Value_Condition (Cnode);
1871 -- If already deleting, then just analyze then statements
1873 if Del then
1874 Analyze_Statements (Tstm);
1876 -- Compile time known value, not deleting yet
1878 elsif Compile_Time_Known_Value (Cond) then
1879 Save_In_Deleted_Code := In_Deleted_Code;
1881 -- If condition is True, then analyze the THEN statements and set
1882 -- no expansion for ELSE and ELSIF parts.
1884 if Is_True (Expr_Value (Cond)) then
1885 Analyze_Statements (Tstm);
1886 Del := True;
1887 Expander_Mode_Save_And_Set (False);
1888 In_Deleted_Code := True;
1890 -- If condition is False, analyze THEN with expansion off
1892 else -- Is_False (Expr_Value (Cond))
1893 Expander_Mode_Save_And_Set (False);
1894 In_Deleted_Code := True;
1895 Analyze_Statements (Tstm);
1896 Expander_Mode_Restore;
1897 In_Deleted_Code := Save_In_Deleted_Code;
1898 end if;
1900 -- Not known at compile time, not deleting, normal analysis
1902 else
1903 Analyze_Statements (Tstm);
1904 end if;
1905 end Analyze_Cond_Then;
1907 -- Start of processing for Analyze_If_Statement
1909 begin
1910 -- Initialize exit count for else statements. If there is no else part,
1911 -- this count will stay non-zero reflecting the fact that the uncovered
1912 -- else case is an unblocked exit.
1914 Unblocked_Exit_Count := 1;
1915 Analyze_Cond_Then (N);
1917 -- Now to analyze the elsif parts if any are present
1919 if Present (Elsif_Parts (N)) then
1920 E := First (Elsif_Parts (N));
1921 while Present (E) loop
1922 Analyze_Cond_Then (E);
1923 Next (E);
1924 end loop;
1925 end if;
1927 if Present (Else_Statements (N)) then
1928 Analyze_Statements (Else_Statements (N));
1929 end if;
1931 -- If all our exits were blocked by unconditional transfers of control,
1932 -- then the entire IF statement acts as an unconditional transfer of
1933 -- control, so treat it like one, and check unreachable code.
1935 if Unblocked_Exit_Count = 0 then
1936 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1937 Check_Unreachable_Code (N);
1938 else
1939 Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1940 end if;
1942 if Del then
1943 Expander_Mode_Restore;
1944 In_Deleted_Code := Save_In_Deleted_Code;
1945 end if;
1947 if not Expander_Active
1948 and then Compile_Time_Known_Value (Condition (N))
1949 and then Serious_Errors_Detected = 0
1950 then
1951 if Is_True (Expr_Value (Condition (N))) then
1952 Remove_Warning_Messages (Else_Statements (N));
1954 if Present (Elsif_Parts (N)) then
1955 E := First (Elsif_Parts (N));
1956 while Present (E) loop
1957 Remove_Warning_Messages (Then_Statements (E));
1958 Next (E);
1959 end loop;
1960 end if;
1962 else
1963 Remove_Warning_Messages (Then_Statements (N));
1964 end if;
1965 end if;
1967 -- Warn on redundant if statement that has no effect
1969 -- Note, we could also check empty ELSIF parts ???
1971 if Warn_On_Redundant_Constructs
1973 -- If statement must be from source
1975 and then Comes_From_Source (N)
1977 -- Condition must not have obvious side effect
1979 and then Has_No_Obvious_Side_Effects (Condition (N))
1981 -- No elsif parts of else part
1983 and then No (Elsif_Parts (N))
1984 and then No (Else_Statements (N))
1986 -- Then must be a single null statement
1988 and then List_Length (Then_Statements (N)) = 1
1989 then
1990 -- Go to original node, since we may have rewritten something as
1991 -- a null statement (e.g. a case we could figure the outcome of).
1993 declare
1994 T : constant Node_Id := First (Then_Statements (N));
1995 S : constant Node_Id := Original_Node (T);
1997 begin
1998 if Comes_From_Source (S) and then Nkind (S) = N_Null_Statement then
1999 Error_Msg_N ("if statement has no effect?r?", N);
2000 end if;
2001 end;
2002 end if;
2003 end Analyze_If_Statement;
2005 ----------------------------------------
2006 -- Analyze_Implicit_Label_Declaration --
2007 ----------------------------------------
2009 -- An implicit label declaration is generated in the innermost enclosing
2010 -- declarative part. This is done for labels, and block and loop names.
2012 -- Note: any changes in this routine may need to be reflected in
2013 -- Analyze_Label_Entity.
2015 procedure Analyze_Implicit_Label_Declaration (N : Node_Id) is
2016 Id : constant Node_Id := Defining_Identifier (N);
2017 begin
2018 Enter_Name (Id);
2019 Set_Ekind (Id, E_Label);
2020 Set_Etype (Id, Standard_Void_Type);
2021 Set_Enclosing_Scope (Id, Current_Scope);
2022 end Analyze_Implicit_Label_Declaration;
2024 ------------------------------
2025 -- Analyze_Iteration_Scheme --
2026 ------------------------------
2028 procedure Analyze_Iteration_Scheme (N : Node_Id) is
2029 Cond : Node_Id;
2030 Iter_Spec : Node_Id;
2031 Loop_Spec : Node_Id;
2033 begin
2034 -- For an infinite loop, there is no iteration scheme
2036 if No (N) then
2037 return;
2038 end if;
2040 Cond := Condition (N);
2041 Iter_Spec := Iterator_Specification (N);
2042 Loop_Spec := Loop_Parameter_Specification (N);
2044 if Present (Cond) then
2045 Analyze_And_Resolve (Cond, Any_Boolean);
2046 Check_Unset_Reference (Cond);
2047 Set_Current_Value_Condition (N);
2049 elsif Present (Iter_Spec) then
2050 Analyze_Iterator_Specification (Iter_Spec);
2052 else
2053 Analyze_Loop_Parameter_Specification (Loop_Spec);
2054 end if;
2055 end Analyze_Iteration_Scheme;
2057 ------------------------------------
2058 -- Analyze_Iterator_Specification --
2059 ------------------------------------
2061 procedure Analyze_Iterator_Specification (N : Node_Id) is
2062 Def_Id : constant Node_Id := Defining_Identifier (N);
2063 Iter_Name : constant Node_Id := Name (N);
2064 Loc : constant Source_Ptr := Sloc (N);
2065 Subt : constant Node_Id := Subtype_Indication (N);
2067 Bas : Entity_Id := Empty; -- initialize to prevent warning
2068 Typ : Entity_Id;
2070 procedure Check_Reverse_Iteration (Typ : Entity_Id);
2071 -- For an iteration over a container, if the loop carries the Reverse
2072 -- indicator, verify that the container type has an Iterate aspect that
2073 -- implements the reversible iterator interface.
2075 procedure Check_Subtype_Indication (Comp_Type : Entity_Id);
2076 -- If a subtype indication is present, verify that it is consistent
2077 -- with the component type of the array or container name.
2079 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id;
2080 -- For containers with Iterator and related aspects, the cursor is
2081 -- obtained by locating an entity with the proper name in the scope
2082 -- of the type.
2084 -----------------------------
2085 -- Check_Reverse_Iteration --
2086 -----------------------------
2088 procedure Check_Reverse_Iteration (Typ : Entity_Id) is
2089 begin
2090 if Reverse_Present (N) then
2091 if Is_Array_Type (Typ)
2092 or else Is_Reversible_Iterator (Typ)
2093 or else
2094 (Present (Find_Aspect (Typ, Aspect_Iterable))
2095 and then
2096 Present
2097 (Get_Iterable_Type_Primitive (Typ, Name_Previous)))
2098 then
2099 null;
2100 else
2101 Error_Msg_NE
2102 ("container type does not support reverse iteration", N, Typ);
2103 end if;
2104 end if;
2105 end Check_Reverse_Iteration;
2107 -------------------------------
2108 -- Check_Subtype_Indication --
2109 -------------------------------
2111 procedure Check_Subtype_Indication (Comp_Type : Entity_Id) is
2112 begin
2113 if Present (Subt)
2114 and then (not Covers (Base_Type ((Bas)), Comp_Type)
2115 or else not Subtypes_Statically_Match (Bas, Comp_Type))
2116 then
2117 if Is_Array_Type (Typ) then
2118 Error_Msg_N
2119 ("subtype indication does not match component type", Subt);
2120 else
2121 Error_Msg_N
2122 ("subtype indication does not match element type", Subt);
2123 end if;
2124 end if;
2125 end Check_Subtype_Indication;
2127 ---------------------
2128 -- Get_Cursor_Type --
2129 ---------------------
2131 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id is
2132 Ent : Entity_Id;
2134 begin
2135 -- If iterator type is derived, the cursor is declared in the scope
2136 -- of the parent type.
2138 if Is_Derived_Type (Typ) then
2139 Ent := First_Entity (Scope (Etype (Typ)));
2140 else
2141 Ent := First_Entity (Scope (Typ));
2142 end if;
2144 while Present (Ent) loop
2145 exit when Chars (Ent) = Name_Cursor;
2146 Next_Entity (Ent);
2147 end loop;
2149 if No (Ent) then
2150 return Any_Type;
2151 end if;
2153 -- The cursor is the target of generated assignments in the
2154 -- loop, and cannot have a limited type.
2156 if Is_Limited_Type (Etype (Ent)) then
2157 Error_Msg_N ("cursor type cannot be limited", N);
2158 end if;
2160 return Etype (Ent);
2161 end Get_Cursor_Type;
2163 -- Start of processing for Analyze_Iterator_Specification
2165 begin
2166 Enter_Name (Def_Id);
2168 -- AI12-0151 specifies that when the subtype indication is present, it
2169 -- must statically match the type of the array or container element.
2170 -- To simplify this check, we introduce a subtype declaration with the
2171 -- given subtype indication when it carries a constraint, and rewrite
2172 -- the original as a reference to the created subtype entity.
2174 if Present (Subt) then
2175 if Nkind (Subt) = N_Subtype_Indication then
2176 declare
2177 S : constant Entity_Id := Make_Temporary (Sloc (Subt), 'S');
2178 Decl : constant Node_Id :=
2179 Make_Subtype_Declaration (Loc,
2180 Defining_Identifier => S,
2181 Subtype_Indication => New_Copy_Tree (Subt));
2182 begin
2183 Insert_Before (Parent (Parent (N)), Decl);
2184 Analyze (Decl);
2185 Rewrite (Subt, New_Occurrence_Of (S, Sloc (Subt)));
2186 end;
2187 else
2188 Analyze (Subt);
2189 end if;
2191 -- Save entity of subtype indication for subsequent check
2193 Bas := Entity (Subt);
2194 end if;
2196 Preanalyze_Range (Iter_Name);
2198 -- Set the kind of the loop variable, which is not visible within the
2199 -- iterator name.
2201 Set_Ekind (Def_Id, E_Variable);
2203 -- Provide a link between the iterator variable and the container, for
2204 -- subsequent use in cross-reference and modification information.
2206 if Of_Present (N) then
2207 Set_Related_Expression (Def_Id, Iter_Name);
2209 -- For a container, the iterator is specified through the aspect
2211 if not Is_Array_Type (Etype (Iter_Name)) then
2212 declare
2213 Iterator : constant Entity_Id :=
2214 Find_Value_Of_Aspect
2215 (Etype (Iter_Name), Aspect_Default_Iterator);
2217 I : Interp_Index;
2218 It : Interp;
2220 begin
2221 if No (Iterator) then
2222 null; -- error reported below
2224 elsif not Is_Overloaded (Iterator) then
2225 Check_Reverse_Iteration (Etype (Iterator));
2227 -- If Iterator is overloaded, use reversible iterator if one is
2228 -- available.
2230 elsif Is_Overloaded (Iterator) then
2231 Get_First_Interp (Iterator, I, It);
2232 while Present (It.Nam) loop
2233 if Ekind (It.Nam) = E_Function
2234 and then Is_Reversible_Iterator (Etype (It.Nam))
2235 then
2236 Set_Etype (Iterator, It.Typ);
2237 Set_Entity (Iterator, It.Nam);
2238 exit;
2239 end if;
2241 Get_Next_Interp (I, It);
2242 end loop;
2244 Check_Reverse_Iteration (Etype (Iterator));
2245 end if;
2246 end;
2247 end if;
2248 end if;
2250 -- If the domain of iteration is an expression, create a declaration for
2251 -- it, so that finalization actions are introduced outside of the loop.
2252 -- The declaration must be a renaming because the body of the loop may
2253 -- assign to elements.
2255 if not Is_Entity_Name (Iter_Name)
2257 -- When the context is a quantified expression, the renaming
2258 -- declaration is delayed until the expansion phase if we are
2259 -- doing expansion.
2261 and then (Nkind (Parent (N)) /= N_Quantified_Expression
2262 or else Operating_Mode = Check_Semantics)
2264 -- Do not perform this expansion for ASIS and when expansion is
2265 -- disabled, where the temporary may hide the transformation of a
2266 -- selected component into a prefixed function call, and references
2267 -- need to see the original expression.
2269 and then Expander_Active
2270 then
2271 declare
2272 Id : constant Entity_Id := Make_Temporary (Loc, 'R', Iter_Name);
2273 Decl : Node_Id;
2274 Act_S : Node_Id;
2276 begin
2278 -- If the domain of iteration is an array component that depends
2279 -- on a discriminant, create actual subtype for it. Pre-analysis
2280 -- does not generate the actual subtype of a selected component.
2282 if Nkind (Iter_Name) = N_Selected_Component
2283 and then Is_Array_Type (Etype (Iter_Name))
2284 then
2285 Act_S :=
2286 Build_Actual_Subtype_Of_Component
2287 (Etype (Selector_Name (Iter_Name)), Iter_Name);
2288 Insert_Action (N, Act_S);
2290 if Present (Act_S) then
2291 Typ := Defining_Identifier (Act_S);
2292 else
2293 Typ := Etype (Iter_Name);
2294 end if;
2296 else
2297 Typ := Etype (Iter_Name);
2299 -- Verify that the expression produces an iterator
2301 if not Of_Present (N) and then not Is_Iterator (Typ)
2302 and then not Is_Array_Type (Typ)
2303 and then No (Find_Aspect (Typ, Aspect_Iterable))
2304 then
2305 Error_Msg_N
2306 ("expect object that implements iterator interface",
2307 Iter_Name);
2308 end if;
2309 end if;
2311 -- Protect against malformed iterator
2313 if Typ = Any_Type then
2314 Error_Msg_N ("invalid expression in loop iterator", Iter_Name);
2315 return;
2316 end if;
2318 if not Of_Present (N) then
2319 Check_Reverse_Iteration (Typ);
2320 end if;
2322 -- The name in the renaming declaration may be a function call.
2323 -- Indicate that it does not come from source, to suppress
2324 -- spurious warnings on renamings of parameterless functions,
2325 -- a common enough idiom in user-defined iterators.
2327 Decl :=
2328 Make_Object_Renaming_Declaration (Loc,
2329 Defining_Identifier => Id,
2330 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
2331 Name =>
2332 New_Copy_Tree (Iter_Name, New_Sloc => Loc));
2334 Insert_Actions (Parent (Parent (N)), New_List (Decl));
2335 Rewrite (Name (N), New_Occurrence_Of (Id, Loc));
2336 Set_Etype (Id, Typ);
2337 Set_Etype (Name (N), Typ);
2338 end;
2340 -- Container is an entity or an array with uncontrolled components, or
2341 -- else it is a container iterator given by a function call, typically
2342 -- called Iterate in the case of predefined containers, even though
2343 -- Iterate is not a reserved name. What matters is that the return type
2344 -- of the function is an iterator type.
2346 elsif Is_Entity_Name (Iter_Name) then
2347 Analyze (Iter_Name);
2349 if Nkind (Iter_Name) = N_Function_Call then
2350 declare
2351 C : constant Node_Id := Name (Iter_Name);
2352 I : Interp_Index;
2353 It : Interp;
2355 begin
2356 if not Is_Overloaded (Iter_Name) then
2357 Resolve (Iter_Name, Etype (C));
2359 else
2360 Get_First_Interp (C, I, It);
2361 while It.Typ /= Empty loop
2362 if Reverse_Present (N) then
2363 if Is_Reversible_Iterator (It.Typ) then
2364 Resolve (Iter_Name, It.Typ);
2365 exit;
2366 end if;
2368 elsif Is_Iterator (It.Typ) then
2369 Resolve (Iter_Name, It.Typ);
2370 exit;
2371 end if;
2373 Get_Next_Interp (I, It);
2374 end loop;
2375 end if;
2376 end;
2378 -- Domain of iteration is not overloaded
2380 else
2381 Resolve (Iter_Name, Etype (Iter_Name));
2382 end if;
2384 if not Of_Present (N) then
2385 Check_Reverse_Iteration (Etype (Iter_Name));
2386 end if;
2387 end if;
2389 -- Get base type of container, for proper retrieval of Cursor type
2390 -- and primitive operations.
2392 Typ := Base_Type (Etype (Iter_Name));
2394 if Is_Array_Type (Typ) then
2395 if Of_Present (N) then
2396 Set_Etype (Def_Id, Component_Type (Typ));
2398 -- The loop variable is aliased if the array components are
2399 -- aliased.
2401 Set_Is_Aliased (Def_Id, Has_Aliased_Components (Typ));
2403 -- AI12-0047 stipulates that the domain (array or container)
2404 -- cannot be a component that depends on a discriminant if the
2405 -- enclosing object is mutable, to prevent a modification of the
2406 -- dowmain of iteration in the course of an iteration.
2408 -- If the object is an expression it has been captured in a
2409 -- temporary, so examine original node.
2411 if Nkind (Original_Node (Iter_Name)) = N_Selected_Component
2412 and then Is_Dependent_Component_Of_Mutable_Object
2413 (Original_Node (Iter_Name))
2414 then
2415 Error_Msg_N
2416 ("iterable name cannot be a discriminant-dependent "
2417 & "component of a mutable object", N);
2418 end if;
2420 Check_Subtype_Indication (Component_Type (Typ));
2422 -- Here we have a missing Range attribute
2424 else
2425 Error_Msg_N
2426 ("missing Range attribute in iteration over an array", N);
2428 -- In Ada 2012 mode, this may be an attempt at an iterator
2430 if Ada_Version >= Ada_2012 then
2431 Error_Msg_NE
2432 ("\if& is meant to designate an element of the array, use OF",
2433 N, Def_Id);
2434 end if;
2436 -- Prevent cascaded errors
2438 Set_Ekind (Def_Id, E_Loop_Parameter);
2439 Set_Etype (Def_Id, Etype (First_Index (Typ)));
2440 end if;
2442 -- Check for type error in iterator
2444 elsif Typ = Any_Type then
2445 return;
2447 -- Iteration over a container
2449 else
2450 Set_Ekind (Def_Id, E_Loop_Parameter);
2451 Error_Msg_Ada_2012_Feature ("container iterator", Sloc (N));
2453 -- OF present
2455 if Of_Present (N) then
2456 if Has_Aspect (Typ, Aspect_Iterable) then
2457 declare
2458 Elt : constant Entity_Id :=
2459 Get_Iterable_Type_Primitive (Typ, Name_Element);
2460 begin
2461 if No (Elt) then
2462 Error_Msg_N
2463 ("missing Element primitive for iteration", N);
2464 else
2465 Set_Etype (Def_Id, Etype (Elt));
2466 Check_Reverse_Iteration (Typ);
2467 end if;
2468 end;
2470 Check_Subtype_Indication (Etype (Def_Id));
2472 -- For a predefined container, The type of the loop variable is
2473 -- the Iterator_Element aspect of the container type.
2475 else
2476 declare
2477 Element : constant Entity_Id :=
2478 Find_Value_Of_Aspect
2479 (Typ, Aspect_Iterator_Element);
2480 Iterator : constant Entity_Id :=
2481 Find_Value_Of_Aspect
2482 (Typ, Aspect_Default_Iterator);
2483 Orig_Iter_Name : constant Node_Id :=
2484 Original_Node (Iter_Name);
2485 Cursor_Type : Entity_Id;
2487 begin
2488 if No (Element) then
2489 Error_Msg_NE ("cannot iterate over&", N, Typ);
2490 return;
2492 else
2493 Set_Etype (Def_Id, Entity (Element));
2494 Cursor_Type := Get_Cursor_Type (Typ);
2495 pragma Assert (Present (Cursor_Type));
2497 Check_Subtype_Indication (Etype (Def_Id));
2499 -- If the container has a variable indexing aspect, the
2500 -- element is a variable and is modifiable in the loop.
2502 if Has_Aspect (Typ, Aspect_Variable_Indexing) then
2503 Set_Ekind (Def_Id, E_Variable);
2504 end if;
2506 -- If the container is a constant, iterating over it
2507 -- requires a Constant_Indexing operation.
2509 if not Is_Variable (Iter_Name)
2510 and then not Has_Aspect (Typ, Aspect_Constant_Indexing)
2511 then
2512 Error_Msg_N
2513 ("iteration over constant container require "
2514 & "constant_indexing aspect", N);
2516 -- The Iterate function may have an in_out parameter,
2517 -- and a constant container is thus illegal.
2519 elsif Present (Iterator)
2520 and then Ekind (Entity (Iterator)) = E_Function
2521 and then Ekind (First_Formal (Entity (Iterator))) /=
2522 E_In_Parameter
2523 and then not Is_Variable (Iter_Name)
2524 then
2525 Error_Msg_N ("variable container expected", N);
2526 end if;
2528 -- Detect a case where the iterator denotes a component
2529 -- of a mutable object which depends on a discriminant.
2530 -- Note that the iterator may denote a function call in
2531 -- qualified form, in which case this check should not
2532 -- be performed.
2534 if Nkind (Orig_Iter_Name) = N_Selected_Component
2535 and then
2536 Present (Entity (Selector_Name (Orig_Iter_Name)))
2537 and then Ekind_In
2538 (Entity (Selector_Name (Orig_Iter_Name)),
2539 E_Component,
2540 E_Discriminant)
2541 and then Is_Dependent_Component_Of_Mutable_Object
2542 (Orig_Iter_Name)
2543 then
2544 Error_Msg_N
2545 ("container cannot be a discriminant-dependent "
2546 & "component of a mutable object", N);
2547 end if;
2548 end if;
2549 end;
2550 end if;
2552 -- IN iterator, domain is a range, or a call to Iterate function
2554 else
2555 -- For an iteration of the form IN, the name must denote an
2556 -- iterator, typically the result of a call to Iterate. Give a
2557 -- useful error message when the name is a container by itself.
2559 -- The type may be a formal container type, which has to have
2560 -- an Iterable aspect detailing the required primitives.
2562 if Is_Entity_Name (Original_Node (Name (N)))
2563 and then not Is_Iterator (Typ)
2564 then
2565 if Has_Aspect (Typ, Aspect_Iterable) then
2566 null;
2568 elsif not Has_Aspect (Typ, Aspect_Iterator_Element) then
2569 Error_Msg_NE
2570 ("cannot iterate over&", Name (N), Typ);
2571 else
2572 Error_Msg_N
2573 ("name must be an iterator, not a container", Name (N));
2574 end if;
2576 if Has_Aspect (Typ, Aspect_Iterable) then
2577 null;
2578 else
2579 Error_Msg_NE
2580 ("\to iterate directly over the elements of a container, "
2581 & "write `of &`", Name (N), Original_Node (Name (N)));
2583 -- No point in continuing analysis of iterator spec
2585 return;
2586 end if;
2587 end if;
2589 -- If the name is a call (typically prefixed) to some Iterate
2590 -- function, it has been rewritten as an object declaration.
2591 -- If that object is a selected component, verify that it is not
2592 -- a component of an unconstrained mutable object.
2594 if Nkind (Iter_Name) = N_Identifier
2595 or else (not Expander_Active and Comes_From_Source (Iter_Name))
2596 then
2597 declare
2598 Orig_Node : constant Node_Id := Original_Node (Iter_Name);
2599 Iter_Kind : constant Node_Kind := Nkind (Orig_Node);
2600 Obj : Node_Id;
2602 begin
2603 if Iter_Kind = N_Selected_Component then
2604 Obj := Prefix (Orig_Node);
2606 elsif Iter_Kind = N_Function_Call then
2607 Obj := First_Actual (Orig_Node);
2609 -- If neither, the name comes from source
2611 else
2612 Obj := Iter_Name;
2613 end if;
2615 if Nkind (Obj) = N_Selected_Component
2616 and then Is_Dependent_Component_Of_Mutable_Object (Obj)
2617 then
2618 Error_Msg_N
2619 ("container cannot be a discriminant-dependent "
2620 & "component of a mutable object", N);
2621 end if;
2622 end;
2623 end if;
2625 -- The result type of Iterate function is the classwide type of
2626 -- the interface parent. We need the specific Cursor type defined
2627 -- in the container package. We obtain it by name for a predefined
2628 -- container, or through the Iterable aspect for a formal one.
2630 if Has_Aspect (Typ, Aspect_Iterable) then
2631 Set_Etype (Def_Id,
2632 Get_Cursor_Type
2633 (Parent (Find_Value_Of_Aspect (Typ, Aspect_Iterable)),
2634 Typ));
2636 else
2637 Set_Etype (Def_Id, Get_Cursor_Type (Typ));
2638 Check_Reverse_Iteration (Etype (Iter_Name));
2639 end if;
2641 end if;
2642 end if;
2643 end Analyze_Iterator_Specification;
2645 -------------------
2646 -- Analyze_Label --
2647 -------------------
2649 -- Note: the semantic work required for analyzing labels (setting them as
2650 -- reachable) was done in a prepass through the statements in the block,
2651 -- so that forward gotos would be properly handled. See Analyze_Statements
2652 -- for further details. The only processing required here is to deal with
2653 -- optimizations that depend on an assumption of sequential control flow,
2654 -- since of course the occurrence of a label breaks this assumption.
2656 procedure Analyze_Label (N : Node_Id) is
2657 pragma Warnings (Off, N);
2658 begin
2659 Kill_Current_Values;
2660 end Analyze_Label;
2662 --------------------------
2663 -- Analyze_Label_Entity --
2664 --------------------------
2666 procedure Analyze_Label_Entity (E : Entity_Id) is
2667 begin
2668 Set_Ekind (E, E_Label);
2669 Set_Etype (E, Standard_Void_Type);
2670 Set_Enclosing_Scope (E, Current_Scope);
2671 Set_Reachable (E, True);
2672 end Analyze_Label_Entity;
2674 ------------------------------------------
2675 -- Analyze_Loop_Parameter_Specification --
2676 ------------------------------------------
2678 procedure Analyze_Loop_Parameter_Specification (N : Node_Id) is
2679 Loop_Nod : constant Node_Id := Parent (Parent (N));
2681 procedure Check_Controlled_Array_Attribute (DS : Node_Id);
2682 -- If the bounds are given by a 'Range reference on a function call
2683 -- that returns a controlled array, introduce an explicit declaration
2684 -- to capture the bounds, so that the function result can be finalized
2685 -- in timely fashion.
2687 procedure Check_Predicate_Use (T : Entity_Id);
2688 -- Diagnose Attempt to iterate through non-static predicate. Note that
2689 -- a type with inherited predicates may have both static and dynamic
2690 -- forms. In this case it is not sufficent to check the static predicate
2691 -- function only, look for a dynamic predicate aspect as well.
2693 function Has_Call_Using_Secondary_Stack (N : Node_Id) return Boolean;
2694 -- N is the node for an arbitrary construct. This function searches the
2695 -- construct N to see if any expressions within it contain function
2696 -- calls that use the secondary stack, returning True if any such call
2697 -- is found, and False otherwise.
2699 procedure Process_Bounds (R : Node_Id);
2700 -- If the iteration is given by a range, create temporaries and
2701 -- assignment statements block to capture the bounds and perform
2702 -- required finalization actions in case a bound includes a function
2703 -- call that uses the temporary stack. We first pre-analyze a copy of
2704 -- the range in order to determine the expected type, and analyze and
2705 -- resolve the original bounds.
2707 --------------------------------------
2708 -- Check_Controlled_Array_Attribute --
2709 --------------------------------------
2711 procedure Check_Controlled_Array_Attribute (DS : Node_Id) is
2712 begin
2713 if Nkind (DS) = N_Attribute_Reference
2714 and then Is_Entity_Name (Prefix (DS))
2715 and then Ekind (Entity (Prefix (DS))) = E_Function
2716 and then Is_Array_Type (Etype (Entity (Prefix (DS))))
2717 and then
2718 Is_Controlled (Component_Type (Etype (Entity (Prefix (DS)))))
2719 and then Expander_Active
2720 then
2721 declare
2722 Loc : constant Source_Ptr := Sloc (N);
2723 Arr : constant Entity_Id := Etype (Entity (Prefix (DS)));
2724 Indx : constant Entity_Id :=
2725 Base_Type (Etype (First_Index (Arr)));
2726 Subt : constant Entity_Id := Make_Temporary (Loc, 'S');
2727 Decl : Node_Id;
2729 begin
2730 Decl :=
2731 Make_Subtype_Declaration (Loc,
2732 Defining_Identifier => Subt,
2733 Subtype_Indication =>
2734 Make_Subtype_Indication (Loc,
2735 Subtype_Mark => New_Occurrence_Of (Indx, Loc),
2736 Constraint =>
2737 Make_Range_Constraint (Loc, Relocate_Node (DS))));
2738 Insert_Before (Loop_Nod, Decl);
2739 Analyze (Decl);
2741 Rewrite (DS,
2742 Make_Attribute_Reference (Loc,
2743 Prefix => New_Occurrence_Of (Subt, Loc),
2744 Attribute_Name => Attribute_Name (DS)));
2746 Analyze (DS);
2747 end;
2748 end if;
2749 end Check_Controlled_Array_Attribute;
2751 -------------------------
2752 -- Check_Predicate_Use --
2753 -------------------------
2755 procedure Check_Predicate_Use (T : Entity_Id) is
2756 begin
2757 -- A predicated subtype is illegal in loops and related constructs
2758 -- if the predicate is not static, or if it is a non-static subtype
2759 -- of a statically predicated subtype.
2761 if Is_Discrete_Type (T)
2762 and then Has_Predicates (T)
2763 and then (not Has_Static_Predicate (T)
2764 or else not Is_Static_Subtype (T)
2765 or else Has_Dynamic_Predicate_Aspect (T))
2766 then
2767 -- Seems a confusing message for the case of a static predicate
2768 -- with a non-static subtype???
2770 Bad_Predicated_Subtype_Use
2771 ("cannot use subtype& with non-static predicate for loop "
2772 & "iteration", Discrete_Subtype_Definition (N),
2773 T, Suggest_Static => True);
2775 elsif Inside_A_Generic
2776 and then Is_Generic_Formal (T)
2777 and then Is_Discrete_Type (T)
2778 then
2779 Set_No_Dynamic_Predicate_On_Actual (T);
2780 end if;
2781 end Check_Predicate_Use;
2783 ------------------------------------
2784 -- Has_Call_Using_Secondary_Stack --
2785 ------------------------------------
2787 function Has_Call_Using_Secondary_Stack (N : Node_Id) return Boolean is
2788 function Check_Call (N : Node_Id) return Traverse_Result;
2789 -- Check if N is a function call which uses the secondary stack
2791 ----------------
2792 -- Check_Call --
2793 ----------------
2795 function Check_Call (N : Node_Id) return Traverse_Result is
2796 Nam : Node_Id;
2797 Subp : Entity_Id;
2798 Typ : Entity_Id;
2800 begin
2801 if Nkind (N) = N_Function_Call then
2802 Nam := Name (N);
2804 -- Obtain the subprogram being invoked
2806 loop
2807 if Nkind (Nam) = N_Explicit_Dereference then
2808 Nam := Prefix (Nam);
2810 elsif Nkind (Nam) = N_Selected_Component then
2811 Nam := Selector_Name (Nam);
2813 else
2814 exit;
2815 end if;
2816 end loop;
2818 Subp := Entity (Nam);
2819 Typ := Etype (Subp);
2821 if Requires_Transient_Scope (Typ) then
2822 return Abandon;
2824 elsif Sec_Stack_Needed_For_Return (Subp) then
2825 return Abandon;
2826 end if;
2827 end if;
2829 -- Continue traversing the tree
2831 return OK;
2832 end Check_Call;
2834 function Check_Calls is new Traverse_Func (Check_Call);
2836 -- Start of processing for Has_Call_Using_Secondary_Stack
2838 begin
2839 return Check_Calls (N) = Abandon;
2840 end Has_Call_Using_Secondary_Stack;
2842 --------------------
2843 -- Process_Bounds --
2844 --------------------
2846 procedure Process_Bounds (R : Node_Id) is
2847 Loc : constant Source_Ptr := Sloc (N);
2849 function One_Bound
2850 (Original_Bound : Node_Id;
2851 Analyzed_Bound : Node_Id;
2852 Typ : Entity_Id) return Node_Id;
2853 -- Capture value of bound and return captured value
2855 ---------------
2856 -- One_Bound --
2857 ---------------
2859 function One_Bound
2860 (Original_Bound : Node_Id;
2861 Analyzed_Bound : Node_Id;
2862 Typ : Entity_Id) return Node_Id
2864 Assign : Node_Id;
2865 Decl : Node_Id;
2866 Id : Entity_Id;
2868 begin
2869 -- If the bound is a constant or an object, no need for a separate
2870 -- declaration. If the bound is the result of previous expansion
2871 -- it is already analyzed and should not be modified. Note that
2872 -- the Bound will be resolved later, if needed, as part of the
2873 -- call to Make_Index (literal bounds may need to be resolved to
2874 -- type Integer).
2876 if Analyzed (Original_Bound) then
2877 return Original_Bound;
2879 elsif Nkind_In (Analyzed_Bound, N_Integer_Literal,
2880 N_Character_Literal)
2881 or else Is_Entity_Name (Analyzed_Bound)
2882 then
2883 Analyze_And_Resolve (Original_Bound, Typ);
2884 return Original_Bound;
2885 end if;
2887 -- Normally, the best approach is simply to generate a constant
2888 -- declaration that captures the bound. However, there is a nasty
2889 -- case where this is wrong. If the bound is complex, and has a
2890 -- possible use of the secondary stack, we need to generate a
2891 -- separate assignment statement to ensure the creation of a block
2892 -- which will release the secondary stack.
2894 -- We prefer the constant declaration, since it leaves us with a
2895 -- proper trace of the value, useful in optimizations that get rid
2896 -- of junk range checks.
2898 if not Has_Call_Using_Secondary_Stack (Analyzed_Bound) then
2899 Analyze_And_Resolve (Original_Bound, Typ);
2901 -- Ensure that the bound is valid. This check should not be
2902 -- generated when the range belongs to a quantified expression
2903 -- as the construct is still not expanded into its final form.
2905 if Nkind (Parent (R)) /= N_Loop_Parameter_Specification
2906 or else Nkind (Parent (Parent (R))) /= N_Quantified_Expression
2907 then
2908 Ensure_Valid (Original_Bound);
2909 end if;
2911 Force_Evaluation (Original_Bound);
2912 return Original_Bound;
2913 end if;
2915 Id := Make_Temporary (Loc, 'R', Original_Bound);
2917 -- Here we make a declaration with a separate assignment
2918 -- statement, and insert before loop header.
2920 Decl :=
2921 Make_Object_Declaration (Loc,
2922 Defining_Identifier => Id,
2923 Object_Definition => New_Occurrence_Of (Typ, Loc));
2925 Assign :=
2926 Make_Assignment_Statement (Loc,
2927 Name => New_Occurrence_Of (Id, Loc),
2928 Expression => Relocate_Node (Original_Bound));
2930 Insert_Actions (Loop_Nod, New_List (Decl, Assign));
2932 -- Now that this temporary variable is initialized we decorate it
2933 -- as safe-to-reevaluate to inform to the backend that no further
2934 -- asignment will be issued and hence it can be handled as side
2935 -- effect free. Note that this decoration must be done when the
2936 -- assignment has been analyzed because otherwise it will be
2937 -- rejected (see Analyze_Assignment).
2939 Set_Is_Safe_To_Reevaluate (Id);
2941 Rewrite (Original_Bound, New_Occurrence_Of (Id, Loc));
2943 if Nkind (Assign) = N_Assignment_Statement then
2944 return Expression (Assign);
2945 else
2946 return Original_Bound;
2947 end if;
2948 end One_Bound;
2950 Hi : constant Node_Id := High_Bound (R);
2951 Lo : constant Node_Id := Low_Bound (R);
2952 R_Copy : constant Node_Id := New_Copy_Tree (R);
2953 New_Hi : Node_Id;
2954 New_Lo : Node_Id;
2955 Typ : Entity_Id;
2957 -- Start of processing for Process_Bounds
2959 begin
2960 Set_Parent (R_Copy, Parent (R));
2961 Preanalyze_Range (R_Copy);
2962 Typ := Etype (R_Copy);
2964 -- If the type of the discrete range is Universal_Integer, then the
2965 -- bound's type must be resolved to Integer, and any object used to
2966 -- hold the bound must also have type Integer, unless the literal
2967 -- bounds are constant-folded expressions with a user-defined type.
2969 if Typ = Universal_Integer then
2970 if Nkind (Lo) = N_Integer_Literal
2971 and then Present (Etype (Lo))
2972 and then Scope (Etype (Lo)) /= Standard_Standard
2973 then
2974 Typ := Etype (Lo);
2976 elsif Nkind (Hi) = N_Integer_Literal
2977 and then Present (Etype (Hi))
2978 and then Scope (Etype (Hi)) /= Standard_Standard
2979 then
2980 Typ := Etype (Hi);
2982 else
2983 Typ := Standard_Integer;
2984 end if;
2985 end if;
2987 Set_Etype (R, Typ);
2989 New_Lo := One_Bound (Lo, Low_Bound (R_Copy), Typ);
2990 New_Hi := One_Bound (Hi, High_Bound (R_Copy), Typ);
2992 -- Propagate staticness to loop range itself, in case the
2993 -- corresponding subtype is static.
2995 if New_Lo /= Lo and then Is_OK_Static_Expression (New_Lo) then
2996 Rewrite (Low_Bound (R), New_Copy (New_Lo));
2997 end if;
2999 if New_Hi /= Hi and then Is_OK_Static_Expression (New_Hi) then
3000 Rewrite (High_Bound (R), New_Copy (New_Hi));
3001 end if;
3002 end Process_Bounds;
3004 -- Local variables
3006 DS : constant Node_Id := Discrete_Subtype_Definition (N);
3007 Id : constant Entity_Id := Defining_Identifier (N);
3009 DS_Copy : Node_Id;
3011 -- Start of processing for Analyze_Loop_Parameter_Specification
3013 begin
3014 Enter_Name (Id);
3016 -- We always consider the loop variable to be referenced, since the loop
3017 -- may be used just for counting purposes.
3019 Generate_Reference (Id, N, ' ');
3021 -- Check for the case of loop variable hiding a local variable (used
3022 -- later on to give a nice warning if the hidden variable is never
3023 -- assigned).
3025 declare
3026 H : constant Entity_Id := Homonym (Id);
3027 begin
3028 if Present (H)
3029 and then Ekind (H) = E_Variable
3030 and then Is_Discrete_Type (Etype (H))
3031 and then Enclosing_Dynamic_Scope (H) = Enclosing_Dynamic_Scope (Id)
3032 then
3033 Set_Hiding_Loop_Variable (H, Id);
3034 end if;
3035 end;
3037 -- Loop parameter specification must include subtype mark in SPARK
3039 if Nkind (DS) = N_Range then
3040 Check_SPARK_05_Restriction
3041 ("loop parameter specification must include subtype mark", N);
3042 end if;
3044 -- Analyze the subtype definition and create temporaries for the bounds.
3045 -- Do not evaluate the range when preanalyzing a quantified expression
3046 -- because bounds expressed as function calls with side effects will be
3047 -- incorrectly replicated.
3049 if Nkind (DS) = N_Range
3050 and then Expander_Active
3051 and then Nkind (Parent (N)) /= N_Quantified_Expression
3052 then
3053 Process_Bounds (DS);
3055 -- Either the expander not active or the range of iteration is a subtype
3056 -- indication, an entity, or a function call that yields an aggregate or
3057 -- a container.
3059 else
3060 DS_Copy := New_Copy_Tree (DS);
3061 Set_Parent (DS_Copy, Parent (DS));
3062 Preanalyze_Range (DS_Copy);
3064 -- Ada 2012: If the domain of iteration is:
3066 -- a) a function call,
3067 -- b) an identifier that is not a type,
3068 -- c) an attribute reference 'Old (within a postcondition),
3069 -- d) an unchecked conversion or a qualified expression with
3070 -- the proper iterator type.
3072 -- then it is an iteration over a container. It was classified as
3073 -- a loop specification by the parser, and must be rewritten now
3074 -- to activate container iteration. The last case will occur within
3075 -- an expanded inlined call, where the expansion wraps an actual in
3076 -- an unchecked conversion when needed. The expression of the
3077 -- conversion is always an object.
3079 if Nkind (DS_Copy) = N_Function_Call
3081 or else (Is_Entity_Name (DS_Copy)
3082 and then not Is_Type (Entity (DS_Copy)))
3084 or else (Nkind (DS_Copy) = N_Attribute_Reference
3085 and then Nam_In (Attribute_Name (DS_Copy),
3086 Name_Loop_Entry, Name_Old))
3088 or else Has_Aspect (Etype (DS_Copy), Aspect_Iterable)
3090 or else Nkind (DS_Copy) = N_Unchecked_Type_Conversion
3091 or else (Nkind (DS_Copy) = N_Qualified_Expression
3092 and then Is_Iterator (Etype (DS_Copy)))
3093 then
3094 -- This is an iterator specification. Rewrite it as such and
3095 -- analyze it to capture function calls that may require
3096 -- finalization actions.
3098 declare
3099 I_Spec : constant Node_Id :=
3100 Make_Iterator_Specification (Sloc (N),
3101 Defining_Identifier => Relocate_Node (Id),
3102 Name => DS_Copy,
3103 Subtype_Indication => Empty,
3104 Reverse_Present => Reverse_Present (N));
3105 Scheme : constant Node_Id := Parent (N);
3107 begin
3108 Set_Iterator_Specification (Scheme, I_Spec);
3109 Set_Loop_Parameter_Specification (Scheme, Empty);
3110 Analyze_Iterator_Specification (I_Spec);
3112 -- In a generic context, analyze the original domain of
3113 -- iteration, for name capture.
3115 if not Expander_Active then
3116 Analyze (DS);
3117 end if;
3119 -- Set kind of loop parameter, which may be used in the
3120 -- subsequent analysis of the condition in a quantified
3121 -- expression.
3123 Set_Ekind (Id, E_Loop_Parameter);
3124 return;
3125 end;
3127 -- Domain of iteration is not a function call, and is side-effect
3128 -- free.
3130 else
3131 -- A quantified expression that appears in a pre/post condition
3132 -- is pre-analyzed several times. If the range is given by an
3133 -- attribute reference it is rewritten as a range, and this is
3134 -- done even with expansion disabled. If the type is already set
3135 -- do not reanalyze, because a range with static bounds may be
3136 -- typed Integer by default.
3138 if Nkind (Parent (N)) = N_Quantified_Expression
3139 and then Present (Etype (DS))
3140 then
3141 null;
3142 else
3143 Analyze (DS);
3144 end if;
3145 end if;
3146 end if;
3148 if DS = Error then
3149 return;
3150 end if;
3152 -- Some additional checks if we are iterating through a type
3154 if Is_Entity_Name (DS)
3155 and then Present (Entity (DS))
3156 and then Is_Type (Entity (DS))
3157 then
3158 -- The subtype indication may denote the completion of an incomplete
3159 -- type declaration.
3161 if Ekind (Entity (DS)) = E_Incomplete_Type then
3162 Set_Entity (DS, Get_Full_View (Entity (DS)));
3163 Set_Etype (DS, Entity (DS));
3164 end if;
3166 Check_Predicate_Use (Entity (DS));
3167 end if;
3169 -- Error if not discrete type
3171 if not Is_Discrete_Type (Etype (DS)) then
3172 Wrong_Type (DS, Any_Discrete);
3173 Set_Etype (DS, Any_Type);
3174 end if;
3176 Check_Controlled_Array_Attribute (DS);
3178 if Nkind (DS) = N_Subtype_Indication then
3179 Check_Predicate_Use (Entity (Subtype_Mark (DS)));
3180 end if;
3182 Make_Index (DS, N, In_Iter_Schm => True);
3183 Set_Ekind (Id, E_Loop_Parameter);
3185 -- A quantified expression which appears in a pre- or post-condition may
3186 -- be analyzed multiple times. The analysis of the range creates several
3187 -- itypes which reside in different scopes depending on whether the pre-
3188 -- or post-condition has been expanded. Update the type of the loop
3189 -- variable to reflect the proper itype at each stage of analysis.
3191 if No (Etype (Id))
3192 or else Etype (Id) = Any_Type
3193 or else
3194 (Present (Etype (Id))
3195 and then Is_Itype (Etype (Id))
3196 and then Nkind (Parent (Loop_Nod)) = N_Expression_With_Actions
3197 and then Nkind (Original_Node (Parent (Loop_Nod))) =
3198 N_Quantified_Expression)
3199 then
3200 Set_Etype (Id, Etype (DS));
3201 end if;
3203 -- Treat a range as an implicit reference to the type, to inhibit
3204 -- spurious warnings.
3206 Generate_Reference (Base_Type (Etype (DS)), N, ' ');
3207 Set_Is_Known_Valid (Id, True);
3209 -- The loop is not a declarative part, so the loop variable must be
3210 -- frozen explicitly. Do not freeze while preanalyzing a quantified
3211 -- expression because the freeze node will not be inserted into the
3212 -- tree due to flag Is_Spec_Expression being set.
3214 if Nkind (Parent (N)) /= N_Quantified_Expression then
3215 declare
3216 Flist : constant List_Id := Freeze_Entity (Id, N);
3217 begin
3218 if Is_Non_Empty_List (Flist) then
3219 Insert_Actions (N, Flist);
3220 end if;
3221 end;
3222 end if;
3224 -- Case where we have a range or a subtype, get type bounds
3226 if Nkind_In (DS, N_Range, N_Subtype_Indication)
3227 and then not Error_Posted (DS)
3228 and then Etype (DS) /= Any_Type
3229 and then Is_Discrete_Type (Etype (DS))
3230 then
3231 declare
3232 L : Node_Id;
3233 H : Node_Id;
3235 begin
3236 if Nkind (DS) = N_Range then
3237 L := Low_Bound (DS);
3238 H := High_Bound (DS);
3239 else
3240 L :=
3241 Type_Low_Bound (Underlying_Type (Etype (Subtype_Mark (DS))));
3242 H :=
3243 Type_High_Bound (Underlying_Type (Etype (Subtype_Mark (DS))));
3244 end if;
3246 -- Check for null or possibly null range and issue warning. We
3247 -- suppress such messages in generic templates and instances,
3248 -- because in practice they tend to be dubious in these cases. The
3249 -- check applies as well to rewritten array element loops where a
3250 -- null range may be detected statically.
3252 if Compile_Time_Compare (L, H, Assume_Valid => True) = GT then
3254 -- Suppress the warning if inside a generic template or
3255 -- instance, since in practice they tend to be dubious in these
3256 -- cases since they can result from intended parameterization.
3258 if not Inside_A_Generic and then not In_Instance then
3260 -- Specialize msg if invalid values could make the loop
3261 -- non-null after all.
3263 if Compile_Time_Compare
3264 (L, H, Assume_Valid => False) = GT
3265 then
3266 -- Since we know the range of the loop is null, set the
3267 -- appropriate flag to remove the loop entirely during
3268 -- expansion.
3270 Set_Is_Null_Loop (Loop_Nod);
3272 if Comes_From_Source (N) then
3273 Error_Msg_N
3274 ("??loop range is null, loop will not execute", DS);
3275 end if;
3277 -- Here is where the loop could execute because of
3278 -- invalid values, so issue appropriate message and in
3279 -- this case we do not set the Is_Null_Loop flag since
3280 -- the loop may execute.
3282 elsif Comes_From_Source (N) then
3283 Error_Msg_N
3284 ("??loop range may be null, loop may not execute",
3285 DS);
3286 Error_Msg_N
3287 ("??can only execute if invalid values are present",
3288 DS);
3289 end if;
3290 end if;
3292 -- In either case, suppress warnings in the body of the loop,
3293 -- since it is likely that these warnings will be inappropriate
3294 -- if the loop never actually executes, which is likely.
3296 Set_Suppress_Loop_Warnings (Loop_Nod);
3298 -- The other case for a warning is a reverse loop where the
3299 -- upper bound is the integer literal zero or one, and the
3300 -- lower bound may exceed this value.
3302 -- For example, we have
3304 -- for J in reverse N .. 1 loop
3306 -- In practice, this is very likely to be a case of reversing
3307 -- the bounds incorrectly in the range.
3309 elsif Reverse_Present (N)
3310 and then Nkind (Original_Node (H)) = N_Integer_Literal
3311 and then
3312 (Intval (Original_Node (H)) = Uint_0
3313 or else
3314 Intval (Original_Node (H)) = Uint_1)
3315 then
3316 -- Lower bound may in fact be known and known not to exceed
3317 -- upper bound (e.g. reverse 0 .. 1) and that's OK.
3319 if Compile_Time_Known_Value (L)
3320 and then Expr_Value (L) <= Expr_Value (H)
3321 then
3322 null;
3324 -- Otherwise warning is warranted
3326 else
3327 Error_Msg_N ("??loop range may be null", DS);
3328 Error_Msg_N ("\??bounds may be wrong way round", DS);
3329 end if;
3330 end if;
3332 -- Check if either bound is known to be outside the range of the
3333 -- loop parameter type, this is e.g. the case of a loop from
3334 -- 20..X where the type is 1..19.
3336 -- Such a loop is dubious since either it raises CE or it executes
3337 -- zero times, and that cannot be useful!
3339 if Etype (DS) /= Any_Type
3340 and then not Error_Posted (DS)
3341 and then Nkind (DS) = N_Subtype_Indication
3342 and then Nkind (Constraint (DS)) = N_Range_Constraint
3343 then
3344 declare
3345 LLo : constant Node_Id :=
3346 Low_Bound (Range_Expression (Constraint (DS)));
3347 LHi : constant Node_Id :=
3348 High_Bound (Range_Expression (Constraint (DS)));
3350 Bad_Bound : Node_Id := Empty;
3351 -- Suspicious loop bound
3353 begin
3354 -- At this stage L, H are the bounds of the type, and LLo
3355 -- Lhi are the low bound and high bound of the loop.
3357 if Compile_Time_Compare (LLo, L, Assume_Valid => True) = LT
3358 or else
3359 Compile_Time_Compare (LLo, H, Assume_Valid => True) = GT
3360 then
3361 Bad_Bound := LLo;
3362 end if;
3364 if Compile_Time_Compare (LHi, L, Assume_Valid => True) = LT
3365 or else
3366 Compile_Time_Compare (LHi, H, Assume_Valid => True) = GT
3367 then
3368 Bad_Bound := LHi;
3369 end if;
3371 if Present (Bad_Bound) then
3372 Error_Msg_N
3373 ("suspicious loop bound out of range of "
3374 & "loop subtype??", Bad_Bound);
3375 Error_Msg_N
3376 ("\loop executes zero times or raises "
3377 & "Constraint_Error??", Bad_Bound);
3378 end if;
3379 end;
3380 end if;
3382 -- This declare block is about warnings, if we get an exception while
3383 -- testing for warnings, we simply abandon the attempt silently. This
3384 -- most likely occurs as the result of a previous error, but might
3385 -- just be an obscure case we have missed. In either case, not giving
3386 -- the warning is perfectly acceptable.
3388 exception
3389 when others => null;
3390 end;
3391 end if;
3393 -- A loop parameter cannot be effectively volatile (SPARK RM 7.1.3(4)).
3394 -- This check is relevant only when SPARK_Mode is on as it is not a
3395 -- standard Ada legality check.
3397 if SPARK_Mode = On and then Is_Effectively_Volatile (Id) then
3398 Error_Msg_N ("loop parameter cannot be volatile", Id);
3399 end if;
3400 end Analyze_Loop_Parameter_Specification;
3402 ----------------------------
3403 -- Analyze_Loop_Statement --
3404 ----------------------------
3406 procedure Analyze_Loop_Statement (N : Node_Id) is
3408 function Is_Container_Iterator (Iter : Node_Id) return Boolean;
3409 -- Given a loop iteration scheme, determine whether it is an Ada 2012
3410 -- container iteration.
3412 function Is_Wrapped_In_Block (N : Node_Id) return Boolean;
3413 -- Determine whether loop statement N has been wrapped in a block to
3414 -- capture finalization actions that may be generated for container
3415 -- iterators. Prevents infinite recursion when block is analyzed.
3416 -- Routine is a noop if loop is single statement within source block.
3418 ---------------------------
3419 -- Is_Container_Iterator --
3420 ---------------------------
3422 function Is_Container_Iterator (Iter : Node_Id) return Boolean is
3423 begin
3424 -- Infinite loop
3426 if No (Iter) then
3427 return False;
3429 -- While loop
3431 elsif Present (Condition (Iter)) then
3432 return False;
3434 -- for Def_Id in [reverse] Name loop
3435 -- for Def_Id [: Subtype_Indication] of [reverse] Name loop
3437 elsif Present (Iterator_Specification (Iter)) then
3438 declare
3439 Nam : constant Node_Id := Name (Iterator_Specification (Iter));
3440 Nam_Copy : Node_Id;
3442 begin
3443 Nam_Copy := New_Copy_Tree (Nam);
3444 Set_Parent (Nam_Copy, Parent (Nam));
3445 Preanalyze_Range (Nam_Copy);
3447 -- The only two options here are iteration over a container or
3448 -- an array.
3450 return not Is_Array_Type (Etype (Nam_Copy));
3451 end;
3453 -- for Def_Id in [reverse] Discrete_Subtype_Definition loop
3455 else
3456 declare
3457 LP : constant Node_Id := Loop_Parameter_Specification (Iter);
3458 DS : constant Node_Id := Discrete_Subtype_Definition (LP);
3459 DS_Copy : Node_Id;
3461 begin
3462 DS_Copy := New_Copy_Tree (DS);
3463 Set_Parent (DS_Copy, Parent (DS));
3464 Preanalyze_Range (DS_Copy);
3466 -- Check for a call to Iterate () or an expression with
3467 -- an iterator type.
3469 return
3470 (Nkind (DS_Copy) = N_Function_Call
3471 and then Needs_Finalization (Etype (DS_Copy)))
3472 or else Is_Iterator (Etype (DS_Copy));
3473 end;
3474 end if;
3475 end Is_Container_Iterator;
3477 -------------------------
3478 -- Is_Wrapped_In_Block --
3479 -------------------------
3481 function Is_Wrapped_In_Block (N : Node_Id) return Boolean is
3482 HSS : Node_Id;
3483 Stat : Node_Id;
3485 begin
3487 -- Check if current scope is a block that is not a transient block.
3489 if Ekind (Current_Scope) /= E_Block
3490 or else No (Block_Node (Current_Scope))
3491 then
3492 return False;
3494 else
3495 HSS :=
3496 Handled_Statement_Sequence (Parent (Block_Node (Current_Scope)));
3498 -- Skip leading pragmas that may be introduced for invariant and
3499 -- predicate checks.
3501 Stat := First (Statements (HSS));
3502 while Present (Stat) and then Nkind (Stat) = N_Pragma loop
3503 Stat := Next (Stat);
3504 end loop;
3506 return Stat = N and then No (Next (Stat));
3507 end if;
3508 end Is_Wrapped_In_Block;
3510 -- Local declarations
3512 Id : constant Node_Id := Identifier (N);
3513 Iter : constant Node_Id := Iteration_Scheme (N);
3514 Loc : constant Source_Ptr := Sloc (N);
3515 Ent : Entity_Id;
3516 Stmt : Node_Id;
3518 -- Start of processing for Analyze_Loop_Statement
3520 begin
3521 if Present (Id) then
3523 -- Make name visible, e.g. for use in exit statements. Loop labels
3524 -- are always considered to be referenced.
3526 Analyze (Id);
3527 Ent := Entity (Id);
3529 -- Guard against serious error (typically, a scope mismatch when
3530 -- semantic analysis is requested) by creating loop entity to
3531 -- continue analysis.
3533 if No (Ent) then
3534 if Total_Errors_Detected /= 0 then
3535 Ent := New_Internal_Entity (E_Loop, Current_Scope, Loc, 'L');
3536 else
3537 raise Program_Error;
3538 end if;
3540 -- Verify that the loop name is hot hidden by an unrelated
3541 -- declaration in an inner scope.
3543 elsif Ekind (Ent) /= E_Label and then Ekind (Ent) /= E_Loop then
3544 Error_Msg_Sloc := Sloc (Ent);
3545 Error_Msg_N ("implicit label declaration for & is hidden#", Id);
3547 if Present (Homonym (Ent))
3548 and then Ekind (Homonym (Ent)) = E_Label
3549 then
3550 Set_Entity (Id, Ent);
3551 Set_Ekind (Ent, E_Loop);
3552 end if;
3554 else
3555 Generate_Reference (Ent, N, ' ');
3556 Generate_Definition (Ent);
3558 -- If we found a label, mark its type. If not, ignore it, since it
3559 -- means we have a conflicting declaration, which would already
3560 -- have been diagnosed at declaration time. Set Label_Construct
3561 -- of the implicit label declaration, which is not created by the
3562 -- parser for generic units.
3564 if Ekind (Ent) = E_Label then
3565 Set_Ekind (Ent, E_Loop);
3567 if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
3568 Set_Label_Construct (Parent (Ent), N);
3569 end if;
3570 end if;
3571 end if;
3573 -- Case of no identifier present. Create one and attach it to the
3574 -- loop statement for use as a scope and as a reference for later
3575 -- expansions. Indicate that the label does not come from source,
3576 -- and attach it to the loop statement so it is part of the tree,
3577 -- even without a full declaration.
3579 else
3580 Ent := New_Internal_Entity (E_Loop, Current_Scope, Loc, 'L');
3581 Set_Etype (Ent, Standard_Void_Type);
3582 Set_Identifier (N, New_Occurrence_Of (Ent, Loc));
3583 Set_Parent (Ent, N);
3584 Set_Has_Created_Identifier (N);
3585 end if;
3587 -- If the iterator specification has a syntactic error, transform
3588 -- construct into an infinite loop to prevent a crash and perform
3589 -- some analysis.
3591 if Present (Iter)
3592 and then Present (Iterator_Specification (Iter))
3593 and then Error_Posted (Iterator_Specification (Iter))
3594 then
3595 Set_Iteration_Scheme (N, Empty);
3596 Analyze (N);
3597 return;
3598 end if;
3600 -- Iteration over a container in Ada 2012 involves the creation of a
3601 -- controlled iterator object. Wrap the loop in a block to ensure the
3602 -- timely finalization of the iterator and release of container locks.
3603 -- The same applies to the use of secondary stack when obtaining an
3604 -- iterator.
3606 if Ada_Version >= Ada_2012
3607 and then Is_Container_Iterator (Iter)
3608 and then not Is_Wrapped_In_Block (N)
3609 then
3610 declare
3611 Block_Nod : Node_Id;
3612 Block_Id : Entity_Id;
3614 begin
3615 Block_Nod :=
3616 Make_Block_Statement (Loc,
3617 Declarations => New_List,
3618 Handled_Statement_Sequence =>
3619 Make_Handled_Sequence_Of_Statements (Loc,
3620 Statements => New_List (Relocate_Node (N))));
3622 Add_Block_Identifier (Block_Nod, Block_Id);
3624 -- The expansion of iterator loops generates an iterator in order
3625 -- to traverse the elements of a container:
3627 -- Iter : <iterator type> := Iterate (Container)'reference;
3629 -- The iterator is controlled and returned on the secondary stack.
3630 -- The analysis of the call to Iterate establishes a transient
3631 -- scope to deal with the secondary stack management, but never
3632 -- really creates a physical block as this would kill the iterator
3633 -- too early (see Wrap_Transient_Declaration). To address this
3634 -- case, mark the generated block as needing secondary stack
3635 -- management.
3637 Set_Uses_Sec_Stack (Block_Id);
3639 Rewrite (N, Block_Nod);
3640 Analyze (N);
3641 return;
3642 end;
3643 end if;
3645 -- Kill current values on entry to loop, since statements in the body of
3646 -- the loop may have been executed before the loop is entered. Similarly
3647 -- we kill values after the loop, since we do not know that the body of
3648 -- the loop was executed.
3650 Kill_Current_Values;
3651 Push_Scope (Ent);
3652 Analyze_Iteration_Scheme (Iter);
3654 -- Check for following case which merits a warning if the type E of is
3655 -- a multi-dimensional array (and no explicit subscript ranges present).
3657 -- for J in E'Range
3658 -- for K in E'Range
3660 if Present (Iter)
3661 and then Present (Loop_Parameter_Specification (Iter))
3662 then
3663 declare
3664 LPS : constant Node_Id := Loop_Parameter_Specification (Iter);
3665 DSD : constant Node_Id :=
3666 Original_Node (Discrete_Subtype_Definition (LPS));
3667 begin
3668 if Nkind (DSD) = N_Attribute_Reference
3669 and then Attribute_Name (DSD) = Name_Range
3670 and then No (Expressions (DSD))
3671 then
3672 declare
3673 Typ : constant Entity_Id := Etype (Prefix (DSD));
3674 begin
3675 if Is_Array_Type (Typ)
3676 and then Number_Dimensions (Typ) > 1
3677 and then Nkind (Parent (N)) = N_Loop_Statement
3678 and then Present (Iteration_Scheme (Parent (N)))
3679 then
3680 declare
3681 OIter : constant Node_Id :=
3682 Iteration_Scheme (Parent (N));
3683 OLPS : constant Node_Id :=
3684 Loop_Parameter_Specification (OIter);
3685 ODSD : constant Node_Id :=
3686 Original_Node (Discrete_Subtype_Definition (OLPS));
3687 begin
3688 if Nkind (ODSD) = N_Attribute_Reference
3689 and then Attribute_Name (ODSD) = Name_Range
3690 and then No (Expressions (ODSD))
3691 and then Etype (Prefix (ODSD)) = Typ
3692 then
3693 Error_Msg_Sloc := Sloc (ODSD);
3694 Error_Msg_N
3695 ("inner range same as outer range#??", DSD);
3696 end if;
3697 end;
3698 end if;
3699 end;
3700 end if;
3701 end;
3702 end if;
3704 -- Analyze the statements of the body except in the case of an Ada 2012
3705 -- iterator with the expander active. In this case the expander will do
3706 -- a rewrite of the loop into a while loop. We will then analyze the
3707 -- loop body when we analyze this while loop.
3709 -- We need to do this delay because if the container is for indefinite
3710 -- types the actual subtype of the components will only be determined
3711 -- when the cursor declaration is analyzed.
3713 -- If the expander is not active then we want to analyze the loop body
3714 -- now even in the Ada 2012 iterator case, since the rewriting will not
3715 -- be done. Insert the loop variable in the current scope, if not done
3716 -- when analysing the iteration scheme. Set its kind properly to detect
3717 -- improper uses in the loop body.
3719 -- In GNATprove mode, we do one of the above depending on the kind of
3720 -- loop. If it is an iterator over an array, then we do not analyze the
3721 -- loop now. We will analyze it after it has been rewritten by the
3722 -- special SPARK expansion which is activated in GNATprove mode. We need
3723 -- to do this so that other expansions that should occur in GNATprove
3724 -- mode take into account the specificities of the rewritten loop, in
3725 -- particular the introduction of a renaming (which needs to be
3726 -- expanded).
3728 -- In other cases in GNATprove mode then we want to analyze the loop
3729 -- body now, since no rewriting will occur. Within a generic the
3730 -- GNATprove mode is irrelevant, we must analyze the generic for
3731 -- non-local name capture.
3733 if Present (Iter)
3734 and then Present (Iterator_Specification (Iter))
3735 then
3736 if GNATprove_Mode
3737 and then Is_Iterator_Over_Array (Iterator_Specification (Iter))
3738 and then not Inside_A_Generic
3739 then
3740 null;
3742 elsif not Expander_Active then
3743 declare
3744 I_Spec : constant Node_Id := Iterator_Specification (Iter);
3745 Id : constant Entity_Id := Defining_Identifier (I_Spec);
3747 begin
3748 if Scope (Id) /= Current_Scope then
3749 Enter_Name (Id);
3750 end if;
3752 -- In an element iterator, The loop parameter is a variable if
3753 -- the domain of iteration (container or array) is a variable.
3755 if not Of_Present (I_Spec)
3756 or else not Is_Variable (Name (I_Spec))
3757 then
3758 Set_Ekind (Id, E_Loop_Parameter);
3759 end if;
3760 end;
3762 Analyze_Statements (Statements (N));
3763 end if;
3765 else
3766 -- Pre-Ada2012 for-loops and while loops
3768 Analyze_Statements (Statements (N));
3769 end if;
3771 -- When the iteration scheme of a loop contains attribute 'Loop_Entry,
3772 -- the loop is transformed into a conditional block. Retrieve the loop.
3774 Stmt := N;
3776 if Subject_To_Loop_Entry_Attributes (Stmt) then
3777 Stmt := Find_Loop_In_Conditional_Block (Stmt);
3778 end if;
3780 -- Finish up processing for the loop. We kill all current values, since
3781 -- in general we don't know if the statements in the loop have been
3782 -- executed. We could do a bit better than this with a loop that we
3783 -- know will execute at least once, but it's not worth the trouble and
3784 -- the front end is not in the business of flow tracing.
3786 Process_End_Label (Stmt, 'e', Ent);
3787 End_Scope;
3788 Kill_Current_Values;
3790 -- Check for infinite loop. Skip check for generated code, since it
3791 -- justs waste time and makes debugging the routine called harder.
3793 -- Note that we have to wait till the body of the loop is fully analyzed
3794 -- before making this call, since Check_Infinite_Loop_Warning relies on
3795 -- being able to use semantic visibility information to find references.
3797 if Comes_From_Source (Stmt) then
3798 Check_Infinite_Loop_Warning (Stmt);
3799 end if;
3801 -- Code after loop is unreachable if the loop has no WHILE or FOR and
3802 -- contains no EXIT statements within the body of the loop.
3804 if No (Iter) and then not Has_Exit (Ent) then
3805 Check_Unreachable_Code (Stmt);
3806 end if;
3807 end Analyze_Loop_Statement;
3809 ----------------------------
3810 -- Analyze_Null_Statement --
3811 ----------------------------
3813 -- Note: the semantics of the null statement is implemented by a single
3814 -- null statement, too bad everything isn't as simple as this.
3816 procedure Analyze_Null_Statement (N : Node_Id) is
3817 pragma Warnings (Off, N);
3818 begin
3819 null;
3820 end Analyze_Null_Statement;
3822 -------------------------
3823 -- Analyze_Target_Name --
3824 -------------------------
3826 procedure Analyze_Target_Name (N : Node_Id) is
3827 begin
3828 -- A target name has the type of the left-hand side of the enclosing
3829 -- assignment.
3831 Set_Etype (N, Etype (Name (Current_Assignment)));
3832 end Analyze_Target_Name;
3834 ------------------------
3835 -- Analyze_Statements --
3836 ------------------------
3838 procedure Analyze_Statements (L : List_Id) is
3839 Lab : Entity_Id;
3840 S : Node_Id;
3842 begin
3843 -- The labels declared in the statement list are reachable from
3844 -- statements in the list. We do this as a prepass so that any goto
3845 -- statement will be properly flagged if its target is not reachable.
3846 -- This is not required, but is nice behavior.
3848 S := First (L);
3849 while Present (S) loop
3850 if Nkind (S) = N_Label then
3851 Analyze (Identifier (S));
3852 Lab := Entity (Identifier (S));
3854 -- If we found a label mark it as reachable
3856 if Ekind (Lab) = E_Label then
3857 Generate_Definition (Lab);
3858 Set_Reachable (Lab);
3860 if Nkind (Parent (Lab)) = N_Implicit_Label_Declaration then
3861 Set_Label_Construct (Parent (Lab), S);
3862 end if;
3864 -- If we failed to find a label, it means the implicit declaration
3865 -- of the label was hidden. A for-loop parameter can do this to
3866 -- a label with the same name inside the loop, since the implicit
3867 -- label declaration is in the innermost enclosing body or block
3868 -- statement.
3870 else
3871 Error_Msg_Sloc := Sloc (Lab);
3872 Error_Msg_N
3873 ("implicit label declaration for & is hidden#",
3874 Identifier (S));
3875 end if;
3876 end if;
3878 Next (S);
3879 end loop;
3881 -- Perform semantic analysis on all statements
3883 Conditional_Statements_Begin;
3885 S := First (L);
3886 while Present (S) loop
3887 Analyze (S);
3889 -- Remove dimension in all statements
3891 Remove_Dimension_In_Statement (S);
3892 Next (S);
3893 end loop;
3895 Conditional_Statements_End;
3897 -- Make labels unreachable. Visibility is not sufficient, because labels
3898 -- in one if-branch for example are not reachable from the other branch,
3899 -- even though their declarations are in the enclosing declarative part.
3901 S := First (L);
3902 while Present (S) loop
3903 if Nkind (S) = N_Label then
3904 Set_Reachable (Entity (Identifier (S)), False);
3905 end if;
3907 Next (S);
3908 end loop;
3909 end Analyze_Statements;
3911 ----------------------------
3912 -- Check_Unreachable_Code --
3913 ----------------------------
3915 procedure Check_Unreachable_Code (N : Node_Id) is
3916 Error_Node : Node_Id;
3917 P : Node_Id;
3919 begin
3920 if Is_List_Member (N) and then Comes_From_Source (N) then
3921 declare
3922 Nxt : Node_Id;
3924 begin
3925 Nxt := Original_Node (Next (N));
3927 -- Skip past pragmas
3929 while Nkind (Nxt) = N_Pragma loop
3930 Nxt := Original_Node (Next (Nxt));
3931 end loop;
3933 -- If a label follows us, then we never have dead code, since
3934 -- someone could branch to the label, so we just ignore it, unless
3935 -- we are in formal mode where goto statements are not allowed.
3937 if Nkind (Nxt) = N_Label
3938 and then not Restriction_Check_Required (SPARK_05)
3939 then
3940 return;
3942 -- Otherwise see if we have a real statement following us
3944 elsif Present (Nxt)
3945 and then Comes_From_Source (Nxt)
3946 and then Is_Statement (Nxt)
3947 then
3948 -- Special very annoying exception. If we have a return that
3949 -- follows a raise, then we allow it without a warning, since
3950 -- the Ada RM annoyingly requires a useless return here.
3952 if Nkind (Original_Node (N)) /= N_Raise_Statement
3953 or else Nkind (Nxt) /= N_Simple_Return_Statement
3954 then
3955 -- The rather strange shenanigans with the warning message
3956 -- here reflects the fact that Kill_Dead_Code is very good
3957 -- at removing warnings in deleted code, and this is one
3958 -- warning we would prefer NOT to have removed.
3960 Error_Node := Nxt;
3962 -- If we have unreachable code, analyze and remove the
3963 -- unreachable code, since it is useless and we don't
3964 -- want to generate junk warnings.
3966 -- We skip this step if we are not in code generation mode
3967 -- or CodePeer mode.
3969 -- This is the one case where we remove dead code in the
3970 -- semantics as opposed to the expander, and we do not want
3971 -- to remove code if we are not in code generation mode,
3972 -- since this messes up the ASIS trees or loses useful
3973 -- information in the CodePeer tree.
3975 -- Note that one might react by moving the whole circuit to
3976 -- exp_ch5, but then we lose the warning in -gnatc mode.
3978 if Operating_Mode = Generate_Code
3979 and then not CodePeer_Mode
3980 then
3981 loop
3982 Nxt := Next (N);
3984 -- Quit deleting when we have nothing more to delete
3985 -- or if we hit a label (since someone could transfer
3986 -- control to a label, so we should not delete it).
3988 exit when No (Nxt) or else Nkind (Nxt) = N_Label;
3990 -- Statement/declaration is to be deleted
3992 Analyze (Nxt);
3993 Remove (Nxt);
3994 Kill_Dead_Code (Nxt);
3995 end loop;
3996 end if;
3998 -- Now issue the warning (or error in formal mode)
4000 if Restriction_Check_Required (SPARK_05) then
4001 Check_SPARK_05_Restriction
4002 ("unreachable code is not allowed", Error_Node);
4003 else
4004 Error_Msg
4005 ("??unreachable code!", Sloc (Error_Node), Error_Node);
4006 end if;
4007 end if;
4009 -- If the unconditional transfer of control instruction is the
4010 -- last statement of a sequence, then see if our parent is one of
4011 -- the constructs for which we count unblocked exits, and if so,
4012 -- adjust the count.
4014 else
4015 P := Parent (N);
4017 -- Statements in THEN part or ELSE part of IF statement
4019 if Nkind (P) = N_If_Statement then
4020 null;
4022 -- Statements in ELSIF part of an IF statement
4024 elsif Nkind (P) = N_Elsif_Part then
4025 P := Parent (P);
4026 pragma Assert (Nkind (P) = N_If_Statement);
4028 -- Statements in CASE statement alternative
4030 elsif Nkind (P) = N_Case_Statement_Alternative then
4031 P := Parent (P);
4032 pragma Assert (Nkind (P) = N_Case_Statement);
4034 -- Statements in body of block
4036 elsif Nkind (P) = N_Handled_Sequence_Of_Statements
4037 and then Nkind (Parent (P)) = N_Block_Statement
4038 then
4039 -- The original loop is now placed inside a block statement
4040 -- due to the expansion of attribute 'Loop_Entry. Return as
4041 -- this is not a "real" block for the purposes of exit
4042 -- counting.
4044 if Nkind (N) = N_Loop_Statement
4045 and then Subject_To_Loop_Entry_Attributes (N)
4046 then
4047 return;
4048 end if;
4050 -- Statements in exception handler in a block
4052 elsif Nkind (P) = N_Exception_Handler
4053 and then Nkind (Parent (P)) = N_Handled_Sequence_Of_Statements
4054 and then Nkind (Parent (Parent (P))) = N_Block_Statement
4055 then
4056 null;
4058 -- None of these cases, so return
4060 else
4061 return;
4062 end if;
4064 -- This was one of the cases we are looking for (i.e. the
4065 -- parent construct was IF, CASE or block) so decrement count.
4067 Unblocked_Exit_Count := Unblocked_Exit_Count - 1;
4068 end if;
4069 end;
4070 end if;
4071 end Check_Unreachable_Code;
4073 ----------------------
4074 -- Preanalyze_Range --
4075 ----------------------
4077 procedure Preanalyze_Range (R_Copy : Node_Id) is
4078 Save_Analysis : constant Boolean := Full_Analysis;
4079 Typ : Entity_Id;
4081 begin
4082 Full_Analysis := False;
4083 Expander_Mode_Save_And_Set (False);
4085 -- In addition to the above we must ecplicity suppress the
4086 -- generation of freeze nodes which might otherwise be generated
4087 -- during resolution of the range (e.g. if given by an attribute
4088 -- that will freeze its prefix).
4090 Set_Must_Not_Freeze (R_Copy);
4092 if Nkind (R_Copy) = N_Attribute_Reference then
4093 Set_Must_Not_Freeze (Prefix (R_Copy));
4094 end if;
4096 Analyze (R_Copy);
4098 if Nkind (R_Copy) in N_Subexpr and then Is_Overloaded (R_Copy) then
4100 -- Apply preference rules for range of predefined integer types, or
4101 -- check for array or iterable construct for "of" iterator, or
4102 -- diagnose true ambiguity.
4104 declare
4105 I : Interp_Index;
4106 It : Interp;
4107 Found : Entity_Id := Empty;
4109 begin
4110 Get_First_Interp (R_Copy, I, It);
4111 while Present (It.Typ) loop
4112 if Is_Discrete_Type (It.Typ) then
4113 if No (Found) then
4114 Found := It.Typ;
4115 else
4116 if Scope (Found) = Standard_Standard then
4117 null;
4119 elsif Scope (It.Typ) = Standard_Standard then
4120 Found := It.Typ;
4122 else
4123 -- Both of them are user-defined
4125 Error_Msg_N
4126 ("ambiguous bounds in range of iteration", R_Copy);
4127 Error_Msg_N ("\possible interpretations:", R_Copy);
4128 Error_Msg_NE ("\\} ", R_Copy, Found);
4129 Error_Msg_NE ("\\} ", R_Copy, It.Typ);
4130 exit;
4131 end if;
4132 end if;
4134 elsif Nkind (Parent (R_Copy)) = N_Iterator_Specification
4135 and then Of_Present (Parent (R_Copy))
4136 then
4137 if Is_Array_Type (It.Typ)
4138 or else Has_Aspect (It.Typ, Aspect_Iterator_Element)
4139 or else Has_Aspect (It.Typ, Aspect_Constant_Indexing)
4140 or else Has_Aspect (It.Typ, Aspect_Variable_Indexing)
4141 then
4142 if No (Found) then
4143 Found := It.Typ;
4144 Set_Etype (R_Copy, It.Typ);
4146 else
4147 Error_Msg_N ("ambiguous domain of iteration", R_Copy);
4148 end if;
4149 end if;
4150 end if;
4152 Get_Next_Interp (I, It);
4153 end loop;
4154 end;
4155 end if;
4157 -- Subtype mark in iteration scheme
4159 if Is_Entity_Name (R_Copy) and then Is_Type (Entity (R_Copy)) then
4160 null;
4162 -- Expression in range, or Ada 2012 iterator
4164 elsif Nkind (R_Copy) in N_Subexpr then
4165 Resolve (R_Copy);
4166 Typ := Etype (R_Copy);
4168 if Is_Discrete_Type (Typ) then
4169 null;
4171 -- Check that the resulting object is an iterable container
4173 elsif Has_Aspect (Typ, Aspect_Iterator_Element)
4174 or else Has_Aspect (Typ, Aspect_Constant_Indexing)
4175 or else Has_Aspect (Typ, Aspect_Variable_Indexing)
4176 then
4177 null;
4179 -- The expression may yield an implicit reference to an iterable
4180 -- container. Insert explicit dereference so that proper type is
4181 -- visible in the loop.
4183 elsif Has_Implicit_Dereference (Etype (R_Copy)) then
4184 declare
4185 Disc : Entity_Id;
4187 begin
4188 Disc := First_Discriminant (Typ);
4189 while Present (Disc) loop
4190 if Has_Implicit_Dereference (Disc) then
4191 Build_Explicit_Dereference (R_Copy, Disc);
4192 exit;
4193 end if;
4195 Next_Discriminant (Disc);
4196 end loop;
4197 end;
4199 end if;
4200 end if;
4202 Expander_Mode_Restore;
4203 Full_Analysis := Save_Analysis;
4204 end Preanalyze_Range;
4206 end Sem_Ch5;