OSDN Git Service

2005-11-14 Cyrille Comar <comar@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_ch5.adb
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-2005, 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 2,  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 COPYING.  If not, write --
19 -- to  the  Free Software Foundation,  51  Franklin  Street,  Fifth  Floor, --
20 -- Boston, MA 02110-1301, USA.                                              --
21 --                                                                          --
22 -- GNAT was originally developed  by the GNAT team at  New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
24 --                                                                          --
25 ------------------------------------------------------------------------------
26
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_Util; use Exp_Util;
33 with Freeze;   use Freeze;
34 with Lib.Xref; use Lib.Xref;
35 with Nlists;   use Nlists;
36 with Nmake;    use Nmake;
37 with Opt;      use Opt;
38 with Sem;      use Sem;
39 with Sem_Case; use Sem_Case;
40 with Sem_Ch3;  use Sem_Ch3;
41 with Sem_Ch8;  use Sem_Ch8;
42 with Sem_Disp; use Sem_Disp;
43 with Sem_Eval; use Sem_Eval;
44 with Sem_Res;  use Sem_Res;
45 with Sem_Type; use Sem_Type;
46 with Sem_Util; use Sem_Util;
47 with Sem_Warn; use Sem_Warn;
48 with Stand;    use Stand;
49 with Sinfo;    use Sinfo;
50 with Targparm; use Targparm;
51 with Tbuild;   use Tbuild;
52 with Uintp;    use Uintp;
53
54 package body Sem_Ch5 is
55
56    Unblocked_Exit_Count : Nat := 0;
57    --  This variable is used when processing if statements, case statements,
58    --  and block statements. It counts the number of exit points that are
59    --  not blocked by unconditional transfer instructions (for IF and CASE,
60    --  these are the branches of the conditional, for a block, they are the
61    --  statement sequence of the block, and the statement sequences of any
62    --  exception handlers that are part of the block. When processing is
63    --  complete, if this count is zero, it means that control cannot fall
64    --  through the IF, CASE or block statement. This is used for the
65    --  generation of warning messages. This variable is recursively saved
66    --  on entry to processing the construct, and restored on exit.
67
68    -----------------------
69    -- Local Subprograms --
70    -----------------------
71
72    procedure Analyze_Iteration_Scheme (N : Node_Id);
73
74    ------------------------
75    -- Analyze_Assignment --
76    ------------------------
77
78    procedure Analyze_Assignment (N : Node_Id) is
79       Lhs  : constant Node_Id := Name (N);
80       Rhs  : constant Node_Id := Expression (N);
81       T1   : Entity_Id;
82       T2   : Entity_Id;
83       Decl : Node_Id;
84       Ent  : Entity_Id;
85
86       procedure Diagnose_Non_Variable_Lhs (N : Node_Id);
87       --  N is the node for the left hand side of an assignment, and it
88       --  is not a variable. This routine issues an appropriate diagnostic.
89
90       procedure Set_Assignment_Type
91         (Opnd      : Node_Id;
92          Opnd_Type : in out Entity_Id);
93       --  Opnd is either the Lhs or Rhs of the assignment, and Opnd_Type
94       --  is the nominal subtype. This procedure is used to deal with cases
95       --  where the nominal subtype must be replaced by the actual subtype.
96
97       -------------------------------
98       -- Diagnose_Non_Variable_Lhs --
99       -------------------------------
100
101       procedure Diagnose_Non_Variable_Lhs (N : Node_Id) is
102       begin
103          --  Not worth posting another error if left hand side already
104          --  flagged as being illegal in some respect
105
106          if Error_Posted (N) then
107             return;
108
109          --  Some special bad cases of entity names
110
111          elsif Is_Entity_Name (N) then
112             if Ekind (Entity (N)) = E_In_Parameter then
113                Error_Msg_N
114                  ("assignment to IN mode parameter not allowed", N);
115
116             --  Private declarations in a protected object are turned into
117             --  constants when compiling a protected function.
118
119             elsif Present (Scope (Entity (N)))
120               and then Is_Protected_Type (Scope (Entity (N)))
121               and then
122                 (Ekind (Current_Scope) = E_Function
123                   or else
124                  Ekind (Enclosing_Dynamic_Scope (Current_Scope)) = E_Function)
125             then
126                Error_Msg_N
127                  ("protected function cannot modify protected object", N);
128
129             elsif Ekind (Entity (N)) = E_Loop_Parameter then
130                Error_Msg_N
131                  ("assignment to loop parameter not allowed", N);
132
133             else
134                Error_Msg_N
135                  ("left hand side of assignment must be a variable", N);
136             end if;
137
138          --  For indexed components or selected components, test prefix
139
140          elsif Nkind (N) = N_Indexed_Component then
141             Diagnose_Non_Variable_Lhs (Prefix (N));
142
143          --  Another special case for assignment to discriminant
144
145          elsif Nkind (N) = N_Selected_Component then
146             if Present (Entity (Selector_Name (N)))
147               and then Ekind (Entity (Selector_Name (N))) = E_Discriminant
148             then
149                Error_Msg_N
150                  ("assignment to discriminant not allowed", N);
151             else
152                Diagnose_Non_Variable_Lhs (Prefix (N));
153             end if;
154
155          else
156             --  If we fall through, we have no special message to issue!
157
158             Error_Msg_N ("left hand side of assignment must be a variable", N);
159          end if;
160       end Diagnose_Non_Variable_Lhs;
161
162       -------------------------
163       -- Set_Assignment_Type --
164       -------------------------
165
166       procedure Set_Assignment_Type
167         (Opnd      : Node_Id;
168          Opnd_Type : in out Entity_Id)
169       is
170       begin
171          Require_Entity (Opnd);
172
173          --  If the assignment operand is an in-out or out parameter, then we
174          --  get the actual subtype (needed for the unconstrained case).
175          --  If the operand is the actual in an entry declaration, then within
176          --  the accept statement it is replaced with a local renaming, which
177          --  may also have an actual subtype.
178
179          if Is_Entity_Name (Opnd)
180            and then (Ekind (Entity (Opnd)) = E_Out_Parameter
181                       or else Ekind (Entity (Opnd)) =
182                            E_In_Out_Parameter
183                       or else Ekind (Entity (Opnd)) =
184                            E_Generic_In_Out_Parameter
185                       or else
186                         (Ekind (Entity (Opnd)) = E_Variable
187                           and then Nkind (Parent (Entity (Opnd))) =
188                              N_Object_Renaming_Declaration
189                           and then Nkind (Parent (Parent (Entity (Opnd)))) =
190                              N_Accept_Statement))
191          then
192             Opnd_Type := Get_Actual_Subtype (Opnd);
193
194          --  If assignment operand is a component reference, then we get the
195          --  actual subtype of the component for the unconstrained case.
196
197          elsif
198            (Nkind (Opnd) = N_Selected_Component
199              or else Nkind (Opnd) = N_Explicit_Dereference)
200            and then not Is_Unchecked_Union (Opnd_Type)
201          then
202             Decl := Build_Actual_Subtype_Of_Component (Opnd_Type, Opnd);
203
204             if Present (Decl) then
205                Insert_Action (N, Decl);
206                Mark_Rewrite_Insertion (Decl);
207                Analyze (Decl);
208                Opnd_Type := Defining_Identifier (Decl);
209                Set_Etype (Opnd, Opnd_Type);
210                Freeze_Itype (Opnd_Type, N);
211
212             elsif Is_Constrained (Etype (Opnd)) then
213                Opnd_Type := Etype (Opnd);
214             end if;
215
216          --  For slice, use the constrained subtype created for the slice
217
218          elsif Nkind (Opnd) = N_Slice then
219             Opnd_Type := Etype (Opnd);
220          end if;
221       end Set_Assignment_Type;
222
223    --  Start of processing for Analyze_Assignment
224
225    begin
226       Analyze (Rhs);
227       Analyze (Lhs);
228       T1 := Etype (Lhs);
229
230       --  In the most general case, both Lhs and Rhs can be overloaded, and we
231       --  must compute the intersection of the possible types on each side.
232
233       if Is_Overloaded (Lhs) then
234          declare
235             I  : Interp_Index;
236             It : Interp;
237
238          begin
239             T1 := Any_Type;
240             Get_First_Interp (Lhs, I, It);
241
242             while Present (It.Typ) loop
243                if Has_Compatible_Type (Rhs, It.Typ) then
244                   if T1 /= Any_Type then
245
246                      --  An explicit dereference is overloaded if the prefix
247                      --  is. Try to remove the ambiguity on the prefix, the
248                      --  error will be posted there if the ambiguity is real.
249
250                      if Nkind (Lhs) = N_Explicit_Dereference then
251                         declare
252                            PI    : Interp_Index;
253                            PI1   : Interp_Index := 0;
254                            PIt   : Interp;
255                            Found : Boolean;
256
257                         begin
258                            Found := False;
259                            Get_First_Interp (Prefix (Lhs), PI, PIt);
260
261                            while Present (PIt.Typ) loop
262                               if Is_Access_Type (PIt.Typ)
263                                 and then Has_Compatible_Type
264                                            (Rhs, Designated_Type (PIt.Typ))
265                               then
266                                  if Found then
267                                     PIt :=
268                                       Disambiguate (Prefix (Lhs),
269                                         PI1, PI, Any_Type);
270
271                                     if PIt = No_Interp then
272                                        Error_Msg_N
273                                          ("ambiguous left-hand side"
274                                             & " in assignment", Lhs);
275                                        exit;
276                                     else
277                                        Resolve (Prefix (Lhs), PIt.Typ);
278                                     end if;
279
280                                     exit;
281                                  else
282                                     Found := True;
283                                     PI1 := PI;
284                                  end if;
285                               end if;
286
287                               Get_Next_Interp (PI, PIt);
288                            end loop;
289                         end;
290
291                      else
292                         Error_Msg_N
293                           ("ambiguous left-hand side in assignment", Lhs);
294                         exit;
295                      end if;
296                   else
297                      T1 := It.Typ;
298                   end if;
299                end if;
300
301                Get_Next_Interp (I, It);
302             end loop;
303          end;
304
305          if T1 = Any_Type then
306             Error_Msg_N
307               ("no valid types for left-hand side for assignment", Lhs);
308             return;
309          end if;
310       end if;
311
312       Resolve (Lhs, T1);
313
314       if not Is_Variable (Lhs) then
315          Diagnose_Non_Variable_Lhs (Lhs);
316          return;
317
318       elsif Is_Limited_Type (T1)
319         and then not Assignment_OK (Lhs)
320         and then not Assignment_OK (Original_Node (Lhs))
321       then
322          Error_Msg_N
323            ("left hand of assignment must not be limited type", Lhs);
324          Explain_Limited_Type (T1, Lhs);
325          return;
326       end if;
327
328       --  Resolution may have updated the subtype, in case the left-hand
329       --  side is a private protected component. Use the correct subtype
330       --  to avoid scoping issues in the back-end.
331
332       T1 := Etype (Lhs);
333
334       --  Ada 2005 (AI-50217, AI-326): Check wrong dereference of incomplete
335       --  type. For example:
336
337       --    limited with P;
338       --    package Pkg is
339       --      type Acc is access P.T;
340       --    end Pkg;
341
342       --    with Pkg; use Acc;
343       --    procedure Example is
344       --       A, B : Acc;
345       --    begin
346       --       A.all := B.all;  -- ERROR
347       --    end Example;
348
349       if Nkind (Lhs) = N_Explicit_Dereference
350         and then Ekind (T1) = E_Incomplete_Type
351       then
352          Error_Msg_N ("invalid use of incomplete type", Lhs);
353          return;
354       end if;
355
356       Set_Assignment_Type (Lhs, T1);
357
358       Resolve (Rhs, T1);
359       Check_Unset_Reference (Rhs);
360
361       --  Remaining steps are skipped if Rhs was syntactically in error
362
363       if Rhs = Error then
364          return;
365       end if;
366
367       T2 := Etype (Rhs);
368
369       if not Covers (T1, T2) then
370          Wrong_Type (Rhs, Etype (Lhs));
371          return;
372       end if;
373
374       --  Ada 2005 (AI-326): In case of explicit dereference of incomplete
375       --  types, use the non-limited view if available
376
377       if Nkind (Rhs) = N_Explicit_Dereference
378         and then Ekind (T2) = E_Incomplete_Type
379         and then Is_Tagged_Type (T2)
380         and then Present (Non_Limited_View (T2))
381       then
382          T2 := Non_Limited_View (T2);
383       end if;
384
385       Set_Assignment_Type (Rhs, T2);
386
387       if Total_Errors_Detected /= 0 then
388          if No (T1) then
389             T1 := Any_Type;
390          end if;
391
392          if No (T2) then
393             T2 := Any_Type;
394          end if;
395       end if;
396
397       if T1 = Any_Type or else T2 = Any_Type then
398          return;
399       end if;
400
401       if (Is_Class_Wide_Type (T2) or else Is_Dynamically_Tagged (Rhs))
402         and then not Is_Class_Wide_Type (T1)
403       then
404          Error_Msg_N ("dynamically tagged expression not allowed!", Rhs);
405
406       elsif Is_Class_Wide_Type (T1)
407         and then not Is_Class_Wide_Type (T2)
408         and then not Is_Tag_Indeterminate (Rhs)
409         and then not Is_Dynamically_Tagged (Rhs)
410       then
411          Error_Msg_N ("dynamically tagged expression required!", Rhs);
412       end if;
413
414       --  Tag propagation is done only in semantics mode only. If expansion
415       --  is on, the rhs tag indeterminate function call has been expanded
416       --  and tag propagation would have happened too late, so the
417       --  propagation take place in expand_call instead.
418
419       if not Expander_Active
420         and then Is_Class_Wide_Type (T1)
421         and then Is_Tag_Indeterminate (Rhs)
422       then
423          Propagate_Tag (Lhs, Rhs);
424       end if;
425
426       --  Ada 2005 (AI-230 and AI-385): When the lhs type is an anonymous
427       --  access type, apply an implicit conversion of the rhs to that type
428       --  to force appropriate static and run-time accessibility checks.
429
430       if Ada_Version >= Ada_05
431         and then Ekind (T1) = E_Anonymous_Access_Type
432       then
433          Rewrite (Rhs, Convert_To (T1, Relocate_Node (Rhs)));
434          Analyze_And_Resolve (Rhs, T1);
435       end if;
436
437       --  Ada 2005 (AI-231)
438
439       if Ada_Version >= Ada_05
440         and then Can_Never_Be_Null (T1)
441         and then not Assignment_OK (Lhs)
442       then
443          if Nkind (Rhs) = N_Null then
444             Apply_Compile_Time_Constraint_Error
445               (N   => Rhs,
446                Msg => "(Ada 2005) NULL not allowed in null-excluding objects?",
447                Reason => CE_Null_Not_Allowed);
448             return;
449
450          elsif not Can_Never_Be_Null (T2) then
451             Rewrite (Rhs,
452               Convert_To (T1, Relocate_Node (Rhs)));
453             Analyze_And_Resolve (Rhs, T1);
454          end if;
455       end if;
456
457       if Is_Scalar_Type (T1) then
458          Apply_Scalar_Range_Check (Rhs, Etype (Lhs));
459
460       elsif Is_Array_Type (T1)
461         and then
462           (Nkind (Rhs) /= N_Type_Conversion
463              or else Is_Constrained (Etype (Rhs)))
464       then
465          --  Assignment verifies that the length of the Lsh and Rhs are equal,
466          --  but of course the indices do not have to match. If the right-hand
467          --  side is a type conversion to an unconstrained type, a length check
468          --  is performed on the expression itself during expansion. In rare
469          --  cases, the redundant length check is computed on an index type
470          --  with a different representation, triggering incorrect code in
471          --  the back end.
472
473          Apply_Length_Check (Rhs, Etype (Lhs));
474
475       else
476          --  Discriminant checks are applied in the course of expansion
477
478          null;
479       end if;
480
481       --  Note: modifications of the Lhs may only be recorded after
482       --  checks have been applied.
483
484       Note_Possible_Modification (Lhs);
485
486       --  ??? a real accessibility check is needed when ???
487
488       --  Post warning for useless assignment
489
490       if Warn_On_Redundant_Constructs
491
492          --  We only warn for source constructs
493
494          and then Comes_From_Source (N)
495
496          --  Where the entity is the same on both sides
497
498          and then Is_Entity_Name (Lhs)
499          and then Is_Entity_Name (Original_Node (Rhs))
500          and then Entity (Lhs) = Entity (Original_Node (Rhs))
501
502          --  But exclude the case where the right side was an operation
503          --  that got rewritten (e.g. JUNK + K, where K was known to be
504          --  zero). We don't want to warn in such a case, since it is
505          --  reasonable to write such expressions especially when K is
506          --  defined symbolically in some other package.
507
508         and then Nkind (Original_Node (Rhs)) not in N_Op
509       then
510          Error_Msg_NE
511            ("?useless assignment of & to itself", N, Entity (Lhs));
512       end if;
513
514       --  Check for non-allowed composite assignment
515
516       if not Support_Composite_Assign_On_Target
517         and then (Is_Array_Type (T1) or else Is_Record_Type (T1))
518         and then (not Has_Size_Clause (T1) or else Esize (T1) > 64)
519       then
520          Error_Msg_CRT ("composite assignment", N);
521       end if;
522
523       --  One more step. Let's see if we have a simple assignment of a
524       --  known at compile time value to a simple variable. If so, we
525       --  can record the value as the current value providing that:
526
527       --    We still have a simple assignment statement (no expansion
528       --    activity has modified it in some peculiar manner)
529
530       --    The type is a discrete type
531
532       --    The assignment is to a named entity
533
534       --    The value is known at compile time
535
536       if Nkind (N) /= N_Assignment_Statement
537         or else not Is_Discrete_Type (T1)
538         or else not Is_Entity_Name (Lhs)
539         or else not Compile_Time_Known_Value (Rhs)
540       then
541          return;
542       end if;
543
544       Ent := Entity (Lhs);
545
546       --  Capture value if safe to do so
547
548       if Safe_To_Capture_Value (N, Ent) then
549          Set_Current_Value (Ent, Rhs);
550       end if;
551    end Analyze_Assignment;
552
553    -----------------------------
554    -- Analyze_Block_Statement --
555    -----------------------------
556
557    procedure Analyze_Block_Statement (N : Node_Id) is
558       Decls : constant List_Id := Declarations (N);
559       Id    : constant Node_Id := Identifier (N);
560       HSS   : constant Node_Id := Handled_Statement_Sequence (N);
561
562    begin
563       --  If no handled statement sequence is present, things are really
564       --  messed up, and we just return immediately (this is a defence
565       --  against previous errors).
566
567       if No (HSS) then
568          return;
569       end if;
570
571       --  Normal processing with HSS present
572
573       declare
574          EH  : constant List_Id := Exception_Handlers (HSS);
575          Ent : Entity_Id        := Empty;
576          S   : Entity_Id;
577
578          Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
579          --  Recursively save value of this global, will be restored on exit
580
581       begin
582          --  Initialize unblocked exit count for statements of begin block
583          --  plus one for each excption handler that is present.
584
585          Unblocked_Exit_Count := 1;
586
587          if Present (EH) then
588             Unblocked_Exit_Count := Unblocked_Exit_Count + List_Length (EH);
589          end if;
590
591          --  If a label is present analyze it and mark it as referenced
592
593          if Present (Id) then
594             Analyze (Id);
595             Ent := Entity (Id);
596
597             --  An error defense. If we have an identifier, but no entity,
598             --  then something is wrong. If we have previous errors, then
599             --  just remove the identifier and continue, otherwise raise
600             --  an exception.
601
602             if No (Ent) then
603                if Total_Errors_Detected /= 0 then
604                   Set_Identifier (N, Empty);
605                else
606                   raise Program_Error;
607                end if;
608
609             else
610                Set_Ekind (Ent, E_Block);
611                Generate_Reference (Ent, N, ' ');
612                Generate_Definition (Ent);
613
614                if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
615                   Set_Label_Construct (Parent (Ent), N);
616                end if;
617             end if;
618          end if;
619
620          --  If no entity set, create a label entity
621
622          if No (Ent) then
623             Ent := New_Internal_Entity (E_Block, Current_Scope, Sloc (N), 'B');
624             Set_Identifier (N, New_Occurrence_Of (Ent, Sloc (N)));
625             Set_Parent (Ent, N);
626          end if;
627
628          Set_Etype (Ent, Standard_Void_Type);
629          Set_Block_Node (Ent, Identifier (N));
630          New_Scope (Ent);
631
632          if Present (Decls) then
633             Analyze_Declarations (Decls);
634             Check_Completion;
635          end if;
636
637          Analyze (HSS);
638          Process_End_Label (HSS, 'e', Ent);
639
640          --  If exception handlers are present, then we indicate that
641          --  enclosing scopes contain a block with handlers. We only
642          --  need to mark non-generic scopes.
643
644          if Present (EH) then
645             S := Scope (Ent);
646             loop
647                Set_Has_Nested_Block_With_Handler (S);
648                exit when Is_Overloadable (S)
649                  or else Ekind (S) = E_Package
650                  or else Is_Generic_Unit (S);
651                S := Scope (S);
652             end loop;
653          end if;
654
655          Check_References (Ent);
656          End_Scope;
657
658          if Unblocked_Exit_Count = 0 then
659             Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
660             Check_Unreachable_Code (N);
661          else
662             Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
663          end if;
664       end;
665    end Analyze_Block_Statement;
666
667    ----------------------------
668    -- Analyze_Case_Statement --
669    ----------------------------
670
671    procedure Analyze_Case_Statement (N : Node_Id) is
672       Exp            : Node_Id;
673       Exp_Type       : Entity_Id;
674       Exp_Btype      : Entity_Id;
675       Last_Choice    : Nat;
676       Dont_Care      : Boolean;
677       Others_Present : Boolean;
678
679       Statements_Analyzed : Boolean := False;
680       --  Set True if at least some statement sequences get analyzed.
681       --  If False on exit, means we had a serious error that prevented
682       --  full analysis of the case statement, and as a result it is not
683       --  a good idea to output warning messages about unreachable code.
684
685       Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
686       --  Recursively save value of this global, will be restored on exit
687
688       procedure Non_Static_Choice_Error (Choice : Node_Id);
689       --  Error routine invoked by the generic instantiation below when
690       --  the case statment has a non static choice.
691
692       procedure Process_Statements (Alternative : Node_Id);
693       --  Analyzes all the statements associated to a case alternative.
694       --  Needed by the generic instantiation below.
695
696       package Case_Choices_Processing is new
697         Generic_Choices_Processing
698           (Get_Alternatives          => Alternatives,
699            Get_Choices               => Discrete_Choices,
700            Process_Empty_Choice      => No_OP,
701            Process_Non_Static_Choice => Non_Static_Choice_Error,
702            Process_Associated_Node   => Process_Statements);
703       use Case_Choices_Processing;
704       --  Instantiation of the generic choice processing package
705
706       -----------------------------
707       -- Non_Static_Choice_Error --
708       -----------------------------
709
710       procedure Non_Static_Choice_Error (Choice : Node_Id) is
711       begin
712          Flag_Non_Static_Expr
713            ("choice given in case statement is not static!", Choice);
714       end Non_Static_Choice_Error;
715
716       ------------------------
717       -- Process_Statements --
718       ------------------------
719
720       procedure Process_Statements (Alternative : Node_Id) is
721          Choices : constant List_Id := Discrete_Choices (Alternative);
722          Ent     : Entity_Id;
723
724       begin
725          Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
726          Statements_Analyzed := True;
727
728          --  An interesting optimization. If the case statement expression
729          --  is a simple entity, then we can set the current value within
730          --  an alternative if the alternative has one possible value.
731
732          --    case N is
733          --      when 1      => alpha
734          --      when 2 | 3  => beta
735          --      when others => gamma
736
737          --  Here we know that N is initially 1 within alpha, but for beta
738          --  and gamma, we do not know anything more about the initial value.
739
740          if Is_Entity_Name (Exp) then
741             Ent := Entity (Exp);
742
743             if Ekind (Ent) = E_Variable
744                  or else
745                Ekind (Ent) = E_In_Out_Parameter
746                  or else
747                Ekind (Ent) = E_Out_Parameter
748             then
749                if List_Length (Choices) = 1
750                  and then Nkind (First (Choices)) in N_Subexpr
751                  and then Compile_Time_Known_Value (First (Choices))
752                then
753                   Set_Current_Value (Entity (Exp), First (Choices));
754                end if;
755
756                Analyze_Statements (Statements (Alternative));
757
758                --  After analyzing the case, set the current value to empty
759                --  since we won't know what it is for the next alternative
760                --  (unless reset by this same circuit), or after the case.
761
762                Set_Current_Value (Entity (Exp), Empty);
763                return;
764             end if;
765          end if;
766
767          --  Case where expression is not an entity name of a variable
768
769          Analyze_Statements (Statements (Alternative));
770       end Process_Statements;
771
772       --  Table to record choices. Put after subprograms since we make
773       --  a call to Number_Of_Choices to get the right number of entries.
774
775       Case_Table : Choice_Table_Type (1 .. Number_Of_Choices (N));
776
777    --  Start of processing for Analyze_Case_Statement
778
779    begin
780       Unblocked_Exit_Count := 0;
781       Exp := Expression (N);
782       Analyze (Exp);
783
784       --  The expression must be of any discrete type. In rare cases, the
785       --  expander constructs a case statement whose expression has a private
786       --  type whose full view is discrete. This can happen when generating
787       --  a stream operation for a variant type after the type is frozen,
788       --  when the partial of view of the type of the discriminant is private.
789       --  In that case, use the full view to analyze case alternatives.
790
791       if not Is_Overloaded (Exp)
792         and then not Comes_From_Source (N)
793         and then Is_Private_Type (Etype (Exp))
794         and then Present (Full_View (Etype (Exp)))
795         and then Is_Discrete_Type (Full_View (Etype (Exp)))
796       then
797          Resolve (Exp, Etype (Exp));
798          Exp_Type := Full_View (Etype (Exp));
799
800       else
801          Analyze_And_Resolve (Exp, Any_Discrete);
802          Exp_Type := Etype (Exp);
803       end if;
804
805       Check_Unset_Reference (Exp);
806       Exp_Btype := Base_Type (Exp_Type);
807
808       --  The expression must be of a discrete type which must be determinable
809       --  independently of the context in which the expression occurs, but
810       --  using the fact that the expression must be of a discrete type.
811       --  Moreover, the type this expression must not be a character literal
812       --  (which is always ambiguous) or, for Ada-83, a generic formal type.
813
814       --  If error already reported by Resolve, nothing more to do
815
816       if Exp_Btype = Any_Discrete
817         or else Exp_Btype = Any_Type
818       then
819          return;
820
821       elsif Exp_Btype = Any_Character then
822          Error_Msg_N
823            ("character literal as case expression is ambiguous", Exp);
824          return;
825
826       elsif Ada_Version = Ada_83
827         and then (Is_Generic_Type (Exp_Btype)
828                     or else Is_Generic_Type (Root_Type (Exp_Btype)))
829       then
830          Error_Msg_N
831            ("(Ada 83) case expression cannot be of a generic type", Exp);
832          return;
833       end if;
834
835       --  If the case expression is a formal object of mode in out, then
836       --  treat it as having a nonstatic subtype by forcing use of the base
837       --  type (which has to get passed to Check_Case_Choices below).  Also
838       --  use base type when the case expression is parenthesized.
839
840       if Paren_Count (Exp) > 0
841         or else (Is_Entity_Name (Exp)
842                   and then Ekind (Entity (Exp)) = E_Generic_In_Out_Parameter)
843       then
844          Exp_Type := Exp_Btype;
845       end if;
846
847       --  Call instantiated Analyze_Choices which does the rest of the work
848
849       Analyze_Choices
850         (N, Exp_Type, Case_Table, Last_Choice, Dont_Care, Others_Present);
851
852       if Exp_Type = Universal_Integer and then not Others_Present then
853          Error_Msg_N ("case on universal integer requires OTHERS choice", Exp);
854       end if;
855
856       --  If all our exits were blocked by unconditional transfers of control,
857       --  then the entire CASE statement acts as an unconditional transfer of
858       --  control, so treat it like one, and check unreachable code. Skip this
859       --  test if we had serious errors preventing any statement analysis.
860
861       if Unblocked_Exit_Count = 0 and then Statements_Analyzed then
862          Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
863          Check_Unreachable_Code (N);
864       else
865          Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
866       end if;
867
868       if not Expander_Active
869         and then Compile_Time_Known_Value (Expression (N))
870         and then Serious_Errors_Detected = 0
871       then
872          declare
873             Chosen : constant Node_Id := Find_Static_Alternative (N);
874             Alt    : Node_Id;
875
876          begin
877             Alt := First (Alternatives (N));
878
879             while Present (Alt) loop
880                if Alt /= Chosen then
881                   Remove_Warning_Messages (Statements (Alt));
882                end if;
883
884                Next (Alt);
885             end loop;
886          end;
887       end if;
888    end Analyze_Case_Statement;
889
890    ----------------------------
891    -- Analyze_Exit_Statement --
892    ----------------------------
893
894    --  If the exit includes a name, it must be the name of a currently open
895    --  loop. Otherwise there must be an innermost open loop on the stack,
896    --  to which the statement implicitly refers.
897
898    procedure Analyze_Exit_Statement (N : Node_Id) is
899       Target   : constant Node_Id := Name (N);
900       Cond     : constant Node_Id := Condition (N);
901       Scope_Id : Entity_Id;
902       U_Name   : Entity_Id;
903       Kind     : Entity_Kind;
904
905    begin
906       if No (Cond) then
907          Check_Unreachable_Code (N);
908       end if;
909
910       if Present (Target) then
911          Analyze (Target);
912          U_Name := Entity (Target);
913
914          if not In_Open_Scopes (U_Name) or else Ekind (U_Name) /= E_Loop then
915             Error_Msg_N ("invalid loop name in exit statement", N);
916             return;
917          else
918             Set_Has_Exit (U_Name);
919          end if;
920
921       else
922          U_Name := Empty;
923       end if;
924
925       for J in reverse 0 .. Scope_Stack.Last loop
926          Scope_Id := Scope_Stack.Table (J).Entity;
927          Kind := Ekind (Scope_Id);
928
929          if Kind = E_Loop
930            and then (No (Target) or else Scope_Id = U_Name) then
931             Set_Has_Exit (Scope_Id);
932             exit;
933
934          elsif Kind = E_Block or else Kind = E_Loop then
935             null;
936
937          else
938             Error_Msg_N
939               ("cannot exit from program unit or accept statement", N);
940             exit;
941          end if;
942       end loop;
943
944       --  Verify that if present the condition is a Boolean expression
945
946       if Present (Cond) then
947          Analyze_And_Resolve (Cond, Any_Boolean);
948          Check_Unset_Reference (Cond);
949       end if;
950    end Analyze_Exit_Statement;
951
952    ----------------------------
953    -- Analyze_Goto_Statement --
954    ----------------------------
955
956    procedure Analyze_Goto_Statement (N : Node_Id) is
957       Label       : constant Node_Id := Name (N);
958       Scope_Id    : Entity_Id;
959       Label_Scope : Entity_Id;
960
961    begin
962       Check_Unreachable_Code (N);
963
964       Analyze (Label);
965
966       if Entity (Label) = Any_Id then
967          return;
968
969       elsif Ekind (Entity (Label)) /= E_Label then
970          Error_Msg_N ("target of goto statement must be a label", Label);
971          return;
972
973       elsif not Reachable (Entity (Label)) then
974          Error_Msg_N ("target of goto statement is not reachable", Label);
975          return;
976       end if;
977
978       Label_Scope := Enclosing_Scope (Entity (Label));
979
980       for J in reverse 0 .. Scope_Stack.Last loop
981          Scope_Id := Scope_Stack.Table (J).Entity;
982
983          if Label_Scope = Scope_Id
984            or else (Ekind (Scope_Id) /= E_Block
985                      and then Ekind (Scope_Id) /= E_Loop)
986          then
987             if Scope_Id /= Label_Scope then
988                Error_Msg_N
989                  ("cannot exit from program unit or accept statement", N);
990             end if;
991
992             return;
993          end if;
994       end loop;
995
996       raise Program_Error;
997    end Analyze_Goto_Statement;
998
999    --------------------------
1000    -- Analyze_If_Statement --
1001    --------------------------
1002
1003    --  A special complication arises in the analysis of if statements
1004
1005    --  The expander has circuitry to completely delete code that it
1006    --  can tell will not be executed (as a result of compile time known
1007    --  conditions). In the analyzer, we ensure that code that will be
1008    --  deleted in this manner is analyzed but not expanded. This is
1009    --  obviously more efficient, but more significantly, difficulties
1010    --  arise if code is expanded and then eliminated (e.g. exception
1011    --  table entries disappear). Similarly, itypes generated in deleted
1012    --  code must be frozen from start, because the nodes on which they
1013    --  depend will not be available at the freeze point.
1014
1015    procedure Analyze_If_Statement (N : Node_Id) is
1016       E : Node_Id;
1017
1018       Save_Unblocked_Exit_Count : constant Nat := Unblocked_Exit_Count;
1019       --  Recursively save value of this global, will be restored on exit
1020
1021       Save_In_Deleted_Code : Boolean;
1022
1023       Del : Boolean := False;
1024       --  This flag gets set True if a True condition has been found,
1025       --  which means that remaining ELSE/ELSIF parts are deleted.
1026
1027       procedure Analyze_Cond_Then (Cnode : Node_Id);
1028       --  This is applied to either the N_If_Statement node itself or
1029       --  to an N_Elsif_Part node. It deals with analyzing the condition
1030       --  and the THEN statements associated with it.
1031
1032       -----------------------
1033       -- Analyze_Cond_Then --
1034       -----------------------
1035
1036       procedure Analyze_Cond_Then (Cnode : Node_Id) is
1037          Cond : constant Node_Id := Condition (Cnode);
1038          Tstm : constant List_Id := Then_Statements (Cnode);
1039
1040       begin
1041          Unblocked_Exit_Count := Unblocked_Exit_Count + 1;
1042          Analyze_And_Resolve (Cond, Any_Boolean);
1043          Check_Unset_Reference (Cond);
1044          Check_Possible_Current_Value_Condition (Cnode);
1045
1046          --  If already deleting, then just analyze then statements
1047
1048          if Del then
1049             Analyze_Statements (Tstm);
1050
1051          --  Compile time known value, not deleting yet
1052
1053          elsif Compile_Time_Known_Value (Cond) then
1054             Save_In_Deleted_Code := In_Deleted_Code;
1055
1056             --  If condition is True, then analyze the THEN statements
1057             --  and set no expansion for ELSE and ELSIF parts.
1058
1059             if Is_True (Expr_Value (Cond)) then
1060                Analyze_Statements (Tstm);
1061                Del := True;
1062                Expander_Mode_Save_And_Set (False);
1063                In_Deleted_Code := True;
1064
1065             --  If condition is False, analyze THEN with expansion off
1066
1067             else -- Is_False (Expr_Value (Cond))
1068                Expander_Mode_Save_And_Set (False);
1069                In_Deleted_Code := True;
1070                Analyze_Statements (Tstm);
1071                Expander_Mode_Restore;
1072                In_Deleted_Code := Save_In_Deleted_Code;
1073             end if;
1074
1075          --  Not known at compile time, not deleting, normal analysis
1076
1077          else
1078             Analyze_Statements (Tstm);
1079          end if;
1080       end Analyze_Cond_Then;
1081
1082    --  Start of Analyze_If_Statement
1083
1084    begin
1085       --  Initialize exit count for else statements. If there is no else
1086       --  part, this count will stay non-zero reflecting the fact that the
1087       --  uncovered else case is an unblocked exit.
1088
1089       Unblocked_Exit_Count := 1;
1090       Analyze_Cond_Then (N);
1091
1092       --  Now to analyze the elsif parts if any are present
1093
1094       if Present (Elsif_Parts (N)) then
1095          E := First (Elsif_Parts (N));
1096          while Present (E) loop
1097             Analyze_Cond_Then (E);
1098             Next (E);
1099          end loop;
1100       end if;
1101
1102       if Present (Else_Statements (N)) then
1103          Analyze_Statements (Else_Statements (N));
1104       end if;
1105
1106       --  If all our exits were blocked by unconditional transfers of control,
1107       --  then the entire IF statement acts as an unconditional transfer of
1108       --  control, so treat it like one, and check unreachable code.
1109
1110       if Unblocked_Exit_Count = 0 then
1111          Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1112          Check_Unreachable_Code (N);
1113       else
1114          Unblocked_Exit_Count := Save_Unblocked_Exit_Count;
1115       end if;
1116
1117       if Del then
1118          Expander_Mode_Restore;
1119          In_Deleted_Code := Save_In_Deleted_Code;
1120       end if;
1121
1122       if not Expander_Active
1123         and then Compile_Time_Known_Value (Condition (N))
1124         and then Serious_Errors_Detected = 0
1125       then
1126          if Is_True (Expr_Value (Condition (N))) then
1127             Remove_Warning_Messages (Else_Statements (N));
1128
1129             if Present (Elsif_Parts (N)) then
1130                E := First (Elsif_Parts (N));
1131
1132                while Present (E) loop
1133                   Remove_Warning_Messages (Then_Statements (E));
1134                   Next (E);
1135                end loop;
1136             end if;
1137
1138          else
1139             Remove_Warning_Messages (Then_Statements (N));
1140          end if;
1141       end if;
1142    end Analyze_If_Statement;
1143
1144    ----------------------------------------
1145    -- Analyze_Implicit_Label_Declaration --
1146    ----------------------------------------
1147
1148    --  An implicit label declaration is generated in the innermost
1149    --  enclosing declarative part. This is done for labels as well as
1150    --  block and loop names.
1151
1152    --  Note: any changes in this routine may need to be reflected in
1153    --  Analyze_Label_Entity.
1154
1155    procedure Analyze_Implicit_Label_Declaration (N : Node_Id) is
1156       Id : constant Node_Id := Defining_Identifier (N);
1157    begin
1158       Enter_Name          (Id);
1159       Set_Ekind           (Id, E_Label);
1160       Set_Etype           (Id, Standard_Void_Type);
1161       Set_Enclosing_Scope (Id, Current_Scope);
1162    end Analyze_Implicit_Label_Declaration;
1163
1164    ------------------------------
1165    -- Analyze_Iteration_Scheme --
1166    ------------------------------
1167
1168    procedure Analyze_Iteration_Scheme (N : Node_Id) is
1169
1170       procedure Process_Bounds (R : Node_Id);
1171       --  If the iteration is given by a range, create temporaries and
1172       --  assignment statements block to capture the bounds and perform
1173       --  required finalization actions in case a bound includes a function
1174       --  call that uses the temporary stack. We first pre-analyze a copy of
1175       --  the range in order to determine the expected type, and analyze and
1176       --  resolve the original bounds.
1177
1178       procedure Check_Controlled_Array_Attribute (DS : Node_Id);
1179       --  If the bounds are given by a 'Range reference on a function call
1180       --  that returns a controlled array, introduce an explicit declaration
1181       --  to capture the bounds, so that the function result can be finalized
1182       --  in timely fashion.
1183
1184       --------------------
1185       -- Process_Bounds --
1186       --------------------
1187
1188       procedure Process_Bounds (R : Node_Id) is
1189          Loc          : constant Source_Ptr := Sloc (N);
1190          R_Copy       : constant Node_Id := New_Copy_Tree (R);
1191          Lo           : constant Node_Id := Low_Bound  (R);
1192          Hi           : constant Node_Id := High_Bound (R);
1193          New_Lo_Bound : Node_Id := Empty;
1194          New_Hi_Bound : Node_Id := Empty;
1195          Typ          : Entity_Id;
1196
1197          function One_Bound
1198            (Original_Bound : Node_Id;
1199             Analyzed_Bound : Node_Id) return Node_Id;
1200          --  Create one declaration followed by one assignment statement
1201          --  to capture the value of bound. We create a separate assignment
1202          --  in order to force the creation of a block in case the bound
1203          --  contains a call that uses the secondary stack.
1204
1205          ---------------
1206          -- One_Bound --
1207          ---------------
1208
1209          function One_Bound
1210            (Original_Bound : Node_Id;
1211             Analyzed_Bound : Node_Id) return Node_Id
1212          is
1213             Assign : Node_Id;
1214             Id     : Entity_Id;
1215             Decl   : Node_Id;
1216
1217          begin
1218             --  If the bound is a constant or an object, no need for a separate
1219             --  declaration. If the bound is the result of previous expansion
1220             --  it is already analyzed and should not be modified. Note that
1221             --  the Bound will be resolved later, if needed, as part of the
1222             --  call to Make_Index (literal bounds may need to be resolved to
1223             --  type Integer).
1224
1225             if Analyzed (Original_Bound) then
1226                return Original_Bound;
1227
1228             elsif Nkind (Analyzed_Bound) = N_Integer_Literal
1229               or else Is_Entity_Name (Analyzed_Bound)
1230             then
1231                Analyze_And_Resolve (Original_Bound, Typ);
1232                return Original_Bound;
1233
1234             else
1235                Analyze_And_Resolve (Original_Bound, Typ);
1236             end if;
1237
1238             Id :=
1239               Make_Defining_Identifier (Loc,
1240                 Chars => New_Internal_Name ('S'));
1241
1242             Decl :=
1243               Make_Object_Declaration (Loc,
1244                 Defining_Identifier => Id,
1245                 Object_Definition   => New_Occurrence_Of (Typ, Loc));
1246
1247             Insert_Before (Parent (N), Decl);
1248             Analyze (Decl);
1249
1250             Assign :=
1251               Make_Assignment_Statement (Loc,
1252                 Name        => New_Occurrence_Of (Id, Loc),
1253                 Expression  => Relocate_Node (Original_Bound));
1254
1255             Insert_Before (Parent (N), Assign);
1256             Analyze (Assign);
1257
1258             Rewrite (Original_Bound, New_Occurrence_Of (Id, Loc));
1259
1260             if Nkind (Assign) = N_Assignment_Statement then
1261                return Expression (Assign);
1262             else
1263                return Original_Bound;
1264             end if;
1265          end One_Bound;
1266
1267       --  Start of processing for Process_Bounds
1268
1269       begin
1270          --  Determine expected type of range by analyzing separate copy
1271
1272          Set_Parent (R_Copy, Parent (R));
1273          Pre_Analyze_And_Resolve (R_Copy);
1274          Typ := Etype (R_Copy);
1275
1276          --  If the type of the discrete range is Universal_Integer, then
1277          --  the bound's type must be resolved to Integer, and any object
1278          --  used to hold the bound must also have type Integer.
1279
1280          if Typ = Universal_Integer then
1281             Typ := Standard_Integer;
1282          end if;
1283
1284          Set_Etype (R, Typ);
1285
1286          New_Lo_Bound := One_Bound (Lo, Low_Bound  (R_Copy));
1287          New_Hi_Bound := One_Bound (Hi, High_Bound (R_Copy));
1288
1289          --  Propagate staticness to loop range itself, in case the
1290          --  corresponding subtype is static.
1291
1292          if New_Lo_Bound /= Lo
1293            and then Is_Static_Expression (New_Lo_Bound)
1294          then
1295             Rewrite  (Low_Bound (R), New_Copy (New_Lo_Bound));
1296          end if;
1297
1298          if New_Hi_Bound /= Hi
1299            and then Is_Static_Expression (New_Hi_Bound)
1300          then
1301             Rewrite (High_Bound (R), New_Copy (New_Hi_Bound));
1302          end if;
1303       end Process_Bounds;
1304
1305       --------------------------------------
1306       -- Check_Controlled_Array_Attribute --
1307       --------------------------------------
1308
1309       procedure Check_Controlled_Array_Attribute (DS : Node_Id) is
1310       begin
1311          if Nkind (DS) = N_Attribute_Reference
1312             and then Is_Entity_Name (Prefix (DS))
1313             and then Ekind (Entity (Prefix (DS))) = E_Function
1314             and then Is_Array_Type (Etype (Entity (Prefix (DS))))
1315             and then
1316               Is_Controlled (
1317                 Component_Type (Etype (Entity (Prefix (DS)))))
1318             and then Expander_Active
1319          then
1320             declare
1321                Loc  : constant Source_Ptr := Sloc (N);
1322                Arr  : constant Entity_Id :=
1323                         Etype (Entity (Prefix (DS)));
1324                Indx : constant Entity_Id :=
1325                         Base_Type (Etype (First_Index (Arr)));
1326                Subt : constant Entity_Id :=
1327                         Make_Defining_Identifier
1328                           (Loc, New_Internal_Name ('S'));
1329                Decl : Node_Id;
1330
1331             begin
1332                Decl :=
1333                  Make_Subtype_Declaration (Loc,
1334                    Defining_Identifier => Subt,
1335                    Subtype_Indication  =>
1336                       Make_Subtype_Indication (Loc,
1337                         Subtype_Mark  => New_Reference_To (Indx, Loc),
1338                         Constraint =>
1339                           Make_Range_Constraint (Loc,
1340                             Relocate_Node (DS))));
1341                Insert_Before (Parent (N), Decl);
1342                Analyze (Decl);
1343
1344                Rewrite (DS,
1345                   Make_Attribute_Reference (Loc,
1346                     Prefix => New_Reference_To (Subt, Loc),
1347                     Attribute_Name => Attribute_Name (DS)));
1348                Analyze (DS);
1349             end;
1350          end if;
1351       end Check_Controlled_Array_Attribute;
1352
1353    --  Start of processing for Analyze_Iteration_Scheme
1354
1355    begin
1356       --  For an infinite loop, there is no iteration scheme
1357
1358       if No (N) then
1359          return;
1360
1361       else
1362          declare
1363             Cond : constant Node_Id := Condition (N);
1364
1365          begin
1366             --  For WHILE loop, verify that the condition is a Boolean
1367             --  expression and resolve and check it.
1368
1369             if Present (Cond) then
1370                Analyze_And_Resolve (Cond, Any_Boolean);
1371                Check_Unset_Reference (Cond);
1372
1373             --  Else we have a FOR loop
1374
1375             else
1376                declare
1377                   LP : constant Node_Id   := Loop_Parameter_Specification (N);
1378                   Id : constant Entity_Id := Defining_Identifier (LP);
1379                   DS : constant Node_Id   := Discrete_Subtype_Definition (LP);
1380
1381                begin
1382                   Enter_Name (Id);
1383
1384                   --  We always consider the loop variable to be referenced,
1385                   --  since the loop may be used just for counting purposes.
1386
1387                   Generate_Reference (Id, N, ' ');
1388
1389                   --  Check for case of loop variable hiding a local
1390                   --  variable (used later on to give a nice warning
1391                   --  if the hidden variable is never assigned).
1392
1393                   declare
1394                      H : constant Entity_Id := Homonym (Id);
1395                   begin
1396                      if Present (H)
1397                        and then Enclosing_Dynamic_Scope (H) =
1398                                 Enclosing_Dynamic_Scope (Id)
1399                        and then Ekind (H) = E_Variable
1400                        and then Is_Discrete_Type (Etype (H))
1401                      then
1402                         Set_Hiding_Loop_Variable (H, Id);
1403                      end if;
1404                   end;
1405
1406                   --  Now analyze the subtype definition. If it is
1407                   --  a range, create temporaries for bounds.
1408
1409                   if Nkind (DS) = N_Range
1410                     and then Expander_Active
1411                   then
1412                      Process_Bounds (DS);
1413                   else
1414                      Analyze (DS);
1415                   end if;
1416
1417                   if DS = Error then
1418                      return;
1419                   end if;
1420
1421                   --  The subtype indication may denote the completion
1422                   --  of an incomplete type declaration.
1423
1424                   if Is_Entity_Name (DS)
1425                     and then Present (Entity (DS))
1426                     and then Is_Type (Entity (DS))
1427                     and then Ekind (Entity (DS)) = E_Incomplete_Type
1428                   then
1429                      Set_Entity (DS, Get_Full_View (Entity (DS)));
1430                      Set_Etype  (DS, Entity (DS));
1431                   end if;
1432
1433                   if not Is_Discrete_Type (Etype (DS)) then
1434                      Wrong_Type (DS, Any_Discrete);
1435                      Set_Etype (DS, Any_Type);
1436                   end if;
1437
1438                   Check_Controlled_Array_Attribute (DS);
1439
1440                   Make_Index (DS, LP);
1441
1442                   Set_Ekind          (Id, E_Loop_Parameter);
1443                   Set_Etype          (Id, Etype (DS));
1444                   Set_Is_Known_Valid (Id, True);
1445
1446                   --  The loop is not a declarative part, so the only entity
1447                   --  declared "within" must be frozen explicitly.
1448
1449                   declare
1450                      Flist : constant List_Id := Freeze_Entity (Id, Sloc (N));
1451                   begin
1452                      if Is_Non_Empty_List (Flist) then
1453                         Insert_Actions (N, Flist);
1454                      end if;
1455                   end;
1456
1457                   --  Check for null or possibly null range and issue warning.
1458                   --  We suppress such messages in generic templates and
1459                   --  instances, because in practice they tend to be dubious
1460                   --  in these cases.
1461
1462                   if Nkind (DS) = N_Range
1463                     and then Comes_From_Source (N)
1464                   then
1465                      declare
1466                         L : constant Node_Id := Low_Bound  (DS);
1467                         H : constant Node_Id := High_Bound (DS);
1468
1469                         Llo : Uint;
1470                         Lhi : Uint;
1471                         LOK : Boolean;
1472                         Hlo : Uint;
1473                         Hhi : Uint;
1474                         HOK : Boolean;
1475
1476                      begin
1477                         Determine_Range (L, LOK, Llo, Lhi);
1478                         Determine_Range (H, HOK, Hlo, Hhi);
1479
1480                         --  If range of loop is null, issue warning
1481
1482                         if (LOK and HOK) and then Llo > Hhi then
1483
1484                            --  Suppress the warning if inside a generic
1485                            --  template or instance, since in practice
1486                            --  they tend to be dubious in these cases since
1487                            --  they can result from intended parametrization.
1488
1489                            if not Inside_A_Generic
1490                               and then not In_Instance
1491                            then
1492                               Error_Msg_N
1493                                 ("?loop range is null, loop will not execute",
1494                                  DS);
1495                            end if;
1496
1497                            --  Since we know the range of the loop is null,
1498                            --  set the appropriate flag to suppress any
1499                            --  warnings that would otherwise be issued in
1500                            --  the body of the loop that will not execute.
1501                            --  We do this even in the generic case, since
1502                            --  if it is dubious to warn on the null loop
1503                            --  itself, it is certainly dubious to warn for
1504                            --  conditions that occur inside it!
1505
1506                            Set_Is_Null_Loop (Parent (N));
1507
1508                         --  The other case for a warning is a reverse loop
1509                         --  where the upper bound is the integer literal
1510                         --  zero or one, and the lower bound can be positive.
1511
1512                         --  For example, we have
1513
1514                         --     for J in reverse N .. 1 loop
1515
1516                         --  In practice, this is very likely to be a case
1517                         --  of reversing the bounds incorrectly in the range.
1518
1519                         elsif Reverse_Present (LP)
1520                           and then Nkind (Original_Node (H)) =
1521                                                           N_Integer_Literal
1522                           and then (Intval (H) = Uint_0
1523                                       or else
1524                                     Intval (H) = Uint_1)
1525                           and then Lhi > Hhi
1526                         then
1527                            Error_Msg_N ("?loop range may be null", DS);
1528                            Error_Msg_N ("\?bounds may be wrong way round", DS);
1529                         end if;
1530                      end;
1531                   end if;
1532                end;
1533             end if;
1534          end;
1535       end if;
1536    end Analyze_Iteration_Scheme;
1537
1538    -------------------
1539    -- Analyze_Label --
1540    -------------------
1541
1542    --  Note: the semantic work required for analyzing labels (setting them as
1543    --  reachable) was done in a prepass through the statements in the block,
1544    --  so that forward gotos would be properly handled. See Analyze_Statements
1545    --  for further details. The only processing required here is to deal with
1546    --  optimizations that depend on an assumption of sequential control flow,
1547    --  since of course the occurrence of a label breaks this assumption.
1548
1549    procedure Analyze_Label (N : Node_Id) is
1550       pragma Warnings (Off, N);
1551    begin
1552       Kill_Current_Values;
1553    end Analyze_Label;
1554
1555    --------------------------
1556    -- Analyze_Label_Entity --
1557    --------------------------
1558
1559    procedure Analyze_Label_Entity (E : Entity_Id) is
1560    begin
1561       Set_Ekind           (E, E_Label);
1562       Set_Etype           (E, Standard_Void_Type);
1563       Set_Enclosing_Scope (E, Current_Scope);
1564       Set_Reachable       (E, True);
1565    end Analyze_Label_Entity;
1566
1567    ----------------------------
1568    -- Analyze_Loop_Statement --
1569    ----------------------------
1570
1571    procedure Analyze_Loop_Statement (N : Node_Id) is
1572       Id  : constant Node_Id := Identifier (N);
1573       Ent : Entity_Id;
1574
1575    begin
1576       if Present (Id) then
1577
1578          --  Make name visible, e.g. for use in exit statements. Loop
1579          --  labels are always considered to be referenced.
1580
1581          Analyze (Id);
1582          Ent := Entity (Id);
1583          Generate_Reference  (Ent, N, ' ');
1584          Generate_Definition (Ent);
1585
1586          --  If we found a label, mark its type. If not, ignore it, since it
1587          --  means we have a conflicting declaration, which would already have
1588          --  been diagnosed at declaration time. Set Label_Construct of the
1589          --  implicit label declaration, which is not created by the parser
1590          --  for generic units.
1591
1592          if Ekind (Ent) = E_Label then
1593             Set_Ekind (Ent, E_Loop);
1594
1595             if Nkind (Parent (Ent)) = N_Implicit_Label_Declaration then
1596                Set_Label_Construct (Parent (Ent), N);
1597             end if;
1598          end if;
1599
1600       --  Case of no identifier present
1601
1602       else
1603          Ent := New_Internal_Entity (E_Loop, Current_Scope, Sloc (N), 'L');
1604          Set_Etype (Ent,  Standard_Void_Type);
1605          Set_Parent (Ent, N);
1606       end if;
1607
1608       --  Kill current values on entry to loop, since statements in body
1609       --  of loop may have been executed before the loop is entered.
1610       --  Similarly we kill values after the loop, since we do not know
1611       --  that the body of the loop was executed.
1612
1613       Kill_Current_Values;
1614       New_Scope (Ent);
1615       Analyze_Iteration_Scheme (Iteration_Scheme (N));
1616       Analyze_Statements (Statements (N));
1617       Process_End_Label (N, 'e', Ent);
1618       End_Scope;
1619       Kill_Current_Values;
1620    end Analyze_Loop_Statement;
1621
1622    ----------------------------
1623    -- Analyze_Null_Statement --
1624    ----------------------------
1625
1626    --  Note: the semantics of the null statement is implemented by a single
1627    --  null statement, too bad everything isn't as simple as this!
1628
1629    procedure Analyze_Null_Statement (N : Node_Id) is
1630       pragma Warnings (Off, N);
1631    begin
1632       null;
1633    end Analyze_Null_Statement;
1634
1635    ------------------------
1636    -- Analyze_Statements --
1637    ------------------------
1638
1639    procedure Analyze_Statements (L : List_Id) is
1640       S   : Node_Id;
1641       Lab : Entity_Id;
1642
1643    begin
1644       --  The labels declared in the statement list are reachable from
1645       --  statements in the list. We do this as a prepass so that any
1646       --  goto statement will be properly flagged if its target is not
1647       --  reachable. This is not required, but is nice behavior!
1648
1649       S := First (L);
1650       while Present (S) loop
1651          if Nkind (S) = N_Label then
1652             Analyze (Identifier (S));
1653             Lab := Entity (Identifier (S));
1654
1655             --  If we found a label mark it as reachable
1656
1657             if Ekind (Lab) = E_Label then
1658                Generate_Definition (Lab);
1659                Set_Reachable (Lab);
1660
1661                if Nkind (Parent (Lab)) = N_Implicit_Label_Declaration then
1662                   Set_Label_Construct (Parent (Lab), S);
1663                end if;
1664
1665             --  If we failed to find a label, it means the implicit declaration
1666             --  of the label was hidden.  A for-loop parameter can do this to
1667             --  a label with the same name inside the loop, since the implicit
1668             --  label declaration is in the innermost enclosing body or block
1669             --  statement.
1670
1671             else
1672                Error_Msg_Sloc := Sloc (Lab);
1673                Error_Msg_N
1674                  ("implicit label declaration for & is hidden#",
1675                   Identifier (S));
1676             end if;
1677          end if;
1678
1679          Next (S);
1680       end loop;
1681
1682       --  Perform semantic analysis on all statements
1683
1684       Conditional_Statements_Begin;
1685
1686       S := First (L);
1687       while Present (S) loop
1688          Analyze (S);
1689          Next (S);
1690       end loop;
1691
1692       Conditional_Statements_End;
1693
1694       --  Make labels unreachable. Visibility is not sufficient, because
1695       --  labels in one if-branch for example are not reachable from the
1696       --  other branch, even though their declarations are in the enclosing
1697       --  declarative part.
1698
1699       S := First (L);
1700       while Present (S) loop
1701          if Nkind (S) = N_Label then
1702             Set_Reachable (Entity (Identifier (S)), False);
1703          end if;
1704
1705          Next (S);
1706       end loop;
1707    end Analyze_Statements;
1708
1709    --------------------------------------------
1710    -- Check_Possible_Current_Value_Condition --
1711    --------------------------------------------
1712
1713    procedure Check_Possible_Current_Value_Condition (Cnode : Node_Id) is
1714       Cond : Node_Id;
1715
1716    begin
1717       --  Loop to deal with (ignore for now) any NOT operators present
1718
1719       Cond := Condition (Cnode);
1720       while Nkind (Cond) = N_Op_Not loop
1721          Cond := Right_Opnd (Cond);
1722       end loop;
1723
1724       --  Check possible relational operator
1725
1726       if Nkind (Cond) = N_Op_Eq
1727            or else
1728          Nkind (Cond) = N_Op_Ne
1729            or else
1730          Nkind (Cond) = N_Op_Ge
1731            or else
1732          Nkind (Cond) = N_Op_Le
1733            or else
1734          Nkind (Cond) = N_Op_Gt
1735            or else
1736          Nkind (Cond) = N_Op_Lt
1737       then
1738          if Compile_Time_Known_Value (Right_Opnd (Cond))
1739            and then Nkind (Left_Opnd (Cond)) = N_Identifier
1740          then
1741             declare
1742                Ent : constant Entity_Id := Entity (Left_Opnd (Cond));
1743
1744             begin
1745                if Ekind (Ent) = E_Variable
1746                     or else
1747                   Ekind (Ent) = E_Constant
1748                     or else
1749                   Is_Formal (Ent)
1750                     or else
1751                   Ekind (Ent) = E_Loop_Parameter
1752                then
1753                   --  Here we have a case where the Current_Value field
1754                   --  may need to be set. We set it if it is not already
1755                   --  set to a compile time expression value.
1756
1757                   --  Note that this represents a decision that one
1758                   --  condition blots out another previous one. That's
1759                   --  certainly right if they occur at the same level.
1760                   --  If the second one is nested, then the decision is
1761                   --  neither right nor wrong (it would be equally OK
1762                   --  to leave the outer one in place, or take the new
1763                   --  inner one. Really we should record both, but our
1764                   --  data structures are not that elaborate.
1765
1766                   if Nkind (Current_Value (Ent)) not in N_Subexpr then
1767                      Set_Current_Value (Ent, Cnode);
1768                   end if;
1769                end if;
1770             end;
1771          end if;
1772       end if;
1773    end Check_Possible_Current_Value_Condition;
1774
1775    ----------------------------
1776    -- Check_Unreachable_Code --
1777    ----------------------------
1778
1779    procedure Check_Unreachable_Code (N : Node_Id) is
1780       Error_Loc : Source_Ptr;
1781       P         : Node_Id;
1782
1783    begin
1784       if Is_List_Member (N)
1785         and then Comes_From_Source (N)
1786       then
1787          declare
1788             Nxt : Node_Id;
1789
1790          begin
1791             Nxt := Original_Node (Next (N));
1792
1793             --  If a label follows us, then we never have dead code, since
1794             --  someone could branch to the label, so we just ignore it.
1795
1796             if Nkind (Nxt) = N_Label then
1797                return;
1798
1799             --  Otherwise see if we have a real statement following us
1800
1801             elsif Present (Nxt)
1802               and then Comes_From_Source (Nxt)
1803               and then Is_Statement (Nxt)
1804             then
1805                --  Special very annoying exception. If we have a return that
1806                --  follows a raise, then we allow it without a warning, since
1807                --  the Ada RM annoyingly requires a useless return here!
1808
1809                if Nkind (Original_Node (N)) /= N_Raise_Statement
1810                  or else Nkind (Nxt) /= N_Return_Statement
1811                then
1812                   --  The rather strange shenanigans with the warning message
1813                   --  here reflects the fact that Kill_Dead_Code is very good
1814                   --  at removing warnings in deleted code, and this is one
1815                   --  warning we would prefer NOT to have removed :-)
1816
1817                   Error_Loc := Sloc (Nxt);
1818
1819                   --  If we have unreachable code, analyze and remove the
1820                   --  unreachable code, since it is useless and we don't
1821                   --  want to generate junk warnings.
1822
1823                   --  We skip this step if we are not in code generation mode.
1824                   --  This is the one case where we remove dead code in the
1825                   --  semantics as opposed to the expander, and we do not want
1826                   --  to remove code if we are not in code generation mode,
1827                   --  since this messes up the ASIS trees.
1828
1829                   --  Note that one might react by moving the whole circuit to
1830                   --  exp_ch5, but then we lose the warning in -gnatc mode.
1831
1832                   if Operating_Mode = Generate_Code then
1833                      loop
1834                         Nxt := Next (N);
1835
1836                         --  Quit deleting when we have nothing more to delete
1837                         --  or if we hit a label (since someone could transfer
1838                         --  control to a label, so we should not delete it).
1839
1840                         exit when No (Nxt) or else Nkind (Nxt) = N_Label;
1841
1842                         --  Statement/declaration is to be deleted
1843
1844                         Analyze (Nxt);
1845                         Remove (Nxt);
1846                         Kill_Dead_Code (Nxt);
1847                      end loop;
1848                   end if;
1849
1850                   --  Now issue the warning
1851
1852                   Error_Msg ("?unreachable code", Error_Loc);
1853                end if;
1854
1855             --  If the unconditional transfer of control instruction is
1856             --  the last statement of a sequence, then see if our parent
1857             --  is one of the constructs for which we count unblocked exits,
1858             --  and if so, adjust the count.
1859
1860             else
1861                P := Parent (N);
1862
1863                --  Statements in THEN part or ELSE part of IF statement
1864
1865                if Nkind (P) = N_If_Statement then
1866                   null;
1867
1868                --  Statements in ELSIF part of an IF statement
1869
1870                elsif Nkind (P) = N_Elsif_Part then
1871                   P := Parent (P);
1872                   pragma Assert (Nkind (P) = N_If_Statement);
1873
1874                --  Statements in CASE statement alternative
1875
1876                elsif Nkind (P) = N_Case_Statement_Alternative then
1877                   P := Parent (P);
1878                   pragma Assert (Nkind (P) = N_Case_Statement);
1879
1880                --  Statements in body of block
1881
1882                elsif Nkind (P) = N_Handled_Sequence_Of_Statements
1883                  and then Nkind (Parent (P)) = N_Block_Statement
1884                then
1885                   null;
1886
1887                --  Statements in exception handler in a block
1888
1889                elsif Nkind (P) = N_Exception_Handler
1890                  and then Nkind (Parent (P)) = N_Handled_Sequence_Of_Statements
1891                  and then Nkind (Parent (Parent (P))) = N_Block_Statement
1892                then
1893                   null;
1894
1895                --  None of these cases, so return
1896
1897                else
1898                   return;
1899                end if;
1900
1901                --  This was one of the cases we are looking for (i.e. the
1902                --  parent construct was IF, CASE or block) so decrement count.
1903
1904                Unblocked_Exit_Count := Unblocked_Exit_Count - 1;
1905             end if;
1906          end;
1907       end if;
1908    end Check_Unreachable_Code;
1909
1910 end Sem_Ch5;