OSDN Git Service

2010-10-07 Ed Schonberg <schonberg@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / par-ch5.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                              P A R . C H 5                               --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2010, 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 ------------------------------------------------------------------------------
25
26 pragma Style_Checks (All_Checks);
27 --  Turn off subprogram body ordering check. Subprograms are in order
28 --  by RM section rather than alphabetical
29
30 separate (Par)
31 package body Ch5 is
32
33    --  Local functions, used only in this chapter
34
35    function P_Case_Statement                     return Node_Id;
36    function P_Case_Statement_Alternative         return Node_Id;
37    function P_Exit_Statement                     return Node_Id;
38    function P_Goto_Statement                     return Node_Id;
39    function P_If_Statement                       return Node_Id;
40    function P_Label                              return Node_Id;
41    function P_Loop_Parameter_Specification       return Node_Id;
42    function P_Null_Statement                     return Node_Id;
43
44    function P_Assignment_Statement (LHS : Node_Id)  return Node_Id;
45    --  Parse assignment statement. On entry, the caller has scanned the left
46    --  hand side (passed in as Lhs), and the colon-equal (or some symbol
47    --  taken to be an error equivalent such as equal).
48
49    function P_Begin_Statement (Block_Name : Node_Id := Empty) return Node_Id;
50    --  Parse begin-end statement. If Block_Name is non-Empty on entry, it is
51    --  the N_Identifier node for the label on the block. If Block_Name is
52    --  Empty on entry (the default), then the block statement is unlabeled.
53
54    function P_Declare_Statement (Block_Name : Node_Id := Empty) return Node_Id;
55    --  Parse declare block. If Block_Name is non-Empty on entry, it is
56    --  the N_Identifier node for the label on the block. If Block_Name is
57    --  Empty on entry (the default), then the block statement is unlabeled.
58
59    function P_For_Statement (Loop_Name : Node_Id := Empty) return Node_Id;
60    --  Parse for statement. If Loop_Name is non-Empty on entry, it is
61    --  the N_Identifier node for the label on the loop. If Loop_Name is
62    --  Empty on entry (the default), then the for statement is unlabeled.
63
64    function P_Loop_Statement (Loop_Name : Node_Id := Empty) return Node_Id;
65    --  Parse loop statement. If Loop_Name is non-Empty on entry, it is
66    --  the N_Identifier node for the label on the loop. If Loop_Name is
67    --  Empty on entry (the default), then the loop statement is unlabeled.
68
69    function P_While_Statement (Loop_Name : Node_Id := Empty) return Node_Id;
70    --  Parse while statement. If Loop_Name is non-Empty on entry, it is
71    --  the N_Identifier node for the label on the loop. If Loop_Name is
72    --  Empty on entry (the default), then the while statement is unlabeled.
73
74    function Set_Loop_Block_Name (L : Character) return Name_Id;
75    --  Given a letter 'L' for a loop or 'B' for a block, returns a name
76    --  of the form L_nn or B_nn where nn is a serial number obtained by
77    --  incrementing the variable Loop_Block_Count.
78
79    procedure Then_Scan;
80    --  Scan past THEN token, testing for illegal junk after it
81
82    ---------------------------------
83    -- 5.1  Sequence of Statements --
84    ---------------------------------
85
86    --  SEQUENCE_OF_STATEMENTS ::= STATEMENT {STATEMENT} {LABEL}
87    --  Note: the final label is an Ada2012 addition.
88
89    --  STATEMENT ::=
90    --    {LABEL} SIMPLE_STATEMENT | {LABEL} COMPOUND_STATEMENT
91
92    --  SIMPLE_STATEMENT ::=      NULL_STATEMENT
93    --  | ASSIGNMENT_STATEMENT  | EXIT_STATEMENT
94    --  | GOTO_STATEMENT        | PROCEDURE_CALL_STATEMENT
95    --  | RETURN_STATEMENT      | ENTRY_CALL_STATEMENT
96    --  | REQUEUE_STATEMENT     | DELAY_STATEMENT
97    --  | ABORT_STATEMENT       | RAISE_STATEMENT
98    --  | CODE_STATEMENT
99
100    --  COMPOUND_STATEMENT ::=
101    --    IF_STATEMENT         | CASE_STATEMENT
102    --  | LOOP_STATEMENT       | BLOCK_STATEMENT
103    --  | ACCEPT_STATEMENT     | SELECT_STATEMENT
104
105    --  This procedure scans a sequence of statements. The caller sets SS_Flags
106    --  to indicate acceptable termination conditions for the sequence:
107
108    --    SS_Flags.Eftm Terminate on ELSIF
109    --    SS_Flags.Eltm Terminate on ELSE
110    --    SS_Flags.Extm Terminate on EXCEPTION
111    --    SS_Flags.Ortm Terminate on OR
112    --    SS_Flags.Tatm Terminate on THEN ABORT (Token = ABORT on return)
113    --    SS_Flags.Whtm Terminate on WHEN
114    --    SS_Flags.Unco Unconditional terminate after scanning one statement
115
116    --  In addition, the scan is always terminated by encountering END or the
117    --  end of file (EOF) condition. If one of the six above terminators is
118    --  encountered with the corresponding SS_Flags flag not set, then the
119    --  action taken is as follows:
120
121    --    If the keyword occurs to the left of the expected column of the end
122    --    for the current sequence (as recorded in the current end context),
123    --    then it is assumed to belong to an outer context, and is considered
124    --    to terminate the sequence of statements.
125
126    --    If the keyword occurs to the right of, or in the expected column of
127    --    the end for the current sequence, then an error message is output,
128    --    the keyword together with its associated context is skipped, and
129    --    the statement scan continues until another terminator is found.
130
131    --  Note that the first action means that control can return to the caller
132    --  with Token set to a terminator other than one of those specified by the
133    --  SS parameter. The caller should treat such a case as equivalent to END.
134
135    --  In addition, the flag SS_Flags.Sreq is set to True to indicate that at
136    --  least one real statement (other than a pragma) is required in the
137    --  statement sequence. During the processing of the sequence, this
138    --  flag is manipulated to indicate the current status of the requirement
139    --  for a statement. For example, it is turned off by the occurrence of a
140    --  statement, and back on by a label (which requires a following statement)
141
142    --  Error recovery: cannot raise Error_Resync. If an error occurs during
143    --  parsing a statement, then the scan pointer is advanced past the next
144    --  semicolon and the parse continues.
145
146    function P_Sequence_Of_Statements (SS_Flags : SS_Rec) return List_Id is
147
148       Statement_Required : Boolean;
149       --  This flag indicates if a subsequent statement (other than a pragma)
150       --  is required. It is initialized from the Sreq flag, and modified as
151       --  statements are scanned (a statement turns it off, and a label turns
152       --  it back on again since a statement must follow a label).
153       --  Note : this final requirement is lifted in Ada2012.
154
155       Statement_Seen : Boolean;
156       --  In Ada2012 a label can end a sequence of statements, but the sequence
157       --  cannot contain only labels. This flag is set whenever a label is
158       --  encountered, to enforce this rule at the end of a sequence.
159
160       Declaration_Found : Boolean := False;
161       --  This flag is set True if a declaration is encountered, so that the
162       --  error message about declarations in the statement part is only
163       --  given once for a given sequence of statements.
164
165       Scan_State_Label : Saved_Scan_State;
166       Scan_State       : Saved_Scan_State;
167
168       Statement_List : List_Id;
169       Block_Label    : Name_Id;
170       Id_Node        : Node_Id;
171       Name_Node      : Node_Id;
172
173       procedure Junk_Declaration;
174       --  Procedure called to handle error of declaration encountered in
175       --  statement sequence.
176
177       procedure Test_Statement_Required;
178       --  Flag error if Statement_Required flag set
179
180       ----------------------
181       -- Junk_Declaration --
182       ----------------------
183
184       procedure Junk_Declaration is
185       begin
186          if (not Declaration_Found) or All_Errors_Mode then
187             Error_Msg_SC -- CODEFIX
188               ("declarations must come before BEGIN");
189             Declaration_Found := True;
190          end if;
191
192          Skip_Declaration (Statement_List);
193       end Junk_Declaration;
194
195       -----------------------------
196       -- Test_Statement_Required --
197       -----------------------------
198
199       procedure Test_Statement_Required is
200          function All_Pragmas return Boolean;
201          --  Return True if statement list is all pragmas
202
203          -----------------
204          -- All_Pragmas --
205          -----------------
206
207          function All_Pragmas return Boolean is
208             S : Node_Id;
209          begin
210             S := First (Statement_List);
211             while Present (S) loop
212                if Nkind (S) /= N_Pragma then
213                   return False;
214                else
215                   Next (S);
216                end if;
217             end loop;
218
219             return True;
220          end All_Pragmas;
221
222       --  Start of processing for Test_Statement_Required
223
224       begin
225          if Statement_Required then
226
227             --  Check no statement required after label in Ada 2012, and that
228             --  it is OK to have nothing but pragmas in a statement sequence.
229
230             if Ada_Version >= Ada_2012
231               and then not Is_Empty_List (Statement_List)
232               and then
233                 ((Nkind (Last (Statement_List)) = N_Label
234                    and then Statement_Seen)
235                 or else All_Pragmas)
236             then
237                declare
238                   Null_Stm : constant Node_Id :=
239                                Make_Null_Statement (Token_Ptr);
240                begin
241                   Set_Comes_From_Source (Null_Stm, False);
242                   Append_To (Statement_List, Null_Stm);
243                end;
244
245             --  If not Ada 2012, or not special case above, give error message
246
247             else
248                Error_Msg_BC -- CODEFIX
249                  ("statement expected");
250             end if;
251          end if;
252       end Test_Statement_Required;
253
254    --  Start of processing for P_Sequence_Of_Statements
255
256    begin
257       Statement_List := New_List;
258       Statement_Required := SS_Flags.Sreq;
259       Statement_Seen     := False;
260
261       loop
262          Ignore (Tok_Semicolon);
263
264          begin
265             if Style_Check then
266                Style.Check_Indentation;
267             end if;
268
269             --  Deal with reserved identifier (in assignment or call)
270
271             if Is_Reserved_Identifier then
272                Save_Scan_State (Scan_State); -- at possible bad identifier
273                Scan; -- and scan past it
274
275                --  We have an reserved word which is spelled in identifier
276                --  style, so the question is whether it really is intended
277                --  to be an identifier.
278
279                if
280                   --  If followed by a semicolon, then it is an identifier,
281                   --  with the exception of the cases tested for below.
282
283                   (Token = Tok_Semicolon
284                     and then Prev_Token /= Tok_Return
285                     and then Prev_Token /= Tok_Null
286                     and then Prev_Token /= Tok_Raise
287                     and then Prev_Token /= Tok_End
288                     and then Prev_Token /= Tok_Exit)
289
290                   --  If followed by colon, colon-equal, or dot, then we
291                   --  definitely  have an identifier (could not be reserved)
292
293                   or else Token = Tok_Colon
294                   or else Token = Tok_Colon_Equal
295                   or else Token = Tok_Dot
296
297                   --  Left paren means we have an identifier except for those
298                   --  reserved words that can legitimately be followed by a
299                   --  left paren.
300
301                   or else
302                     (Token = Tok_Left_Paren
303                       and then Prev_Token /= Tok_Case
304                       and then Prev_Token /= Tok_Delay
305                       and then Prev_Token /= Tok_If
306                       and then Prev_Token /= Tok_Elsif
307                       and then Prev_Token /= Tok_Return
308                       and then Prev_Token /= Tok_When
309                       and then Prev_Token /= Tok_While
310                       and then Prev_Token /= Tok_Separate)
311                then
312                   --  Here we have an apparent reserved identifier and the
313                   --  token past it is appropriate to this usage (and would
314                   --  be a definite error if this is not an identifier). What
315                   --  we do is to use P_Identifier to fix up the identifier,
316                   --  and then fall into the normal processing.
317
318                   Restore_Scan_State (Scan_State); -- back to the ID
319                   Scan_Reserved_Identifier (Force_Msg => False);
320
321                   --  Not a reserved identifier after all (or at least we can't
322                   --  be sure that it is), so reset the scan and continue.
323
324                else
325                   Restore_Scan_State (Scan_State); -- back to the reserved word
326                end if;
327             end if;
328
329             --  Now look to see what kind of statement we have
330
331             case Token is
332
333                --  Case of end or EOF
334
335                when Tok_End | Tok_EOF =>
336
337                   --  These tokens always terminate the statement sequence
338
339                   Test_Statement_Required;
340                   exit;
341
342                --  Case of ELSIF
343
344                when Tok_Elsif =>
345
346                   --  Terminate if Eftm set or if the ELSIF is to the left
347                   --  of the expected column of the end for this sequence
348
349                   if SS_Flags.Eftm
350                      or else Start_Column < Scope.Table (Scope.Last).Ecol
351                   then
352                      Test_Statement_Required;
353                      exit;
354
355                   --  Otherwise complain and skip past ELSIF Condition then
356
357                   else
358                      Error_Msg_SC ("ELSIF not allowed here");
359                      Scan; -- past ELSIF
360                      Discard_Junk_Node (P_Expression_No_Right_Paren);
361                      Then_Scan;
362                      Statement_Required := False;
363                   end if;
364
365                --  Case of ELSE
366
367                when Tok_Else =>
368
369                   --  Terminate if Eltm set or if the else is to the left
370                   --  of the expected column of the end for this sequence
371
372                   if SS_Flags.Eltm
373                      or else Start_Column < Scope.Table (Scope.Last).Ecol
374                   then
375                      Test_Statement_Required;
376                      exit;
377
378                   --  Otherwise complain and skip past else
379
380                   else
381                      Error_Msg_SC ("ELSE not allowed here");
382                      Scan; -- past ELSE
383                      Statement_Required := False;
384                   end if;
385
386                --  Case of exception
387
388                when Tok_Exception =>
389                   Test_Statement_Required;
390
391                   --  If Extm not set and the exception is not to the left of
392                   --  the expected column of the end for this sequence, then we
393                   --  assume it belongs to the current sequence, even though it
394                   --  is not permitted.
395
396                   if not SS_Flags.Extm and then
397                      Start_Column >= Scope.Table (Scope.Last).Ecol
398
399                   then
400                      Error_Msg_SC ("exception handler not permitted here");
401                      Scan; -- past EXCEPTION
402                      Discard_Junk_List (Parse_Exception_Handlers);
403                   end if;
404
405                   --  Always return, in the case where we scanned out handlers
406                   --  that we did not expect, Parse_Exception_Handlers returned
407                   --  with Token being either end or EOF, so we are OK.
408
409                   exit;
410
411                --  Case of OR
412
413                when Tok_Or =>
414
415                   --  Terminate if Ortm set or if the or is to the left of the
416                   --  expected column of the end for this sequence.
417
418                   if SS_Flags.Ortm
419                      or else Start_Column < Scope.Table (Scope.Last).Ecol
420                   then
421                      Test_Statement_Required;
422                      exit;
423
424                   --  Otherwise complain and skip past or
425
426                   else
427                      Error_Msg_SC ("OR not allowed here");
428                      Scan; -- past or
429                      Statement_Required := False;
430                   end if;
431
432                --  Case of THEN (deal also with THEN ABORT)
433
434                when Tok_Then =>
435                   Save_Scan_State (Scan_State); -- at THEN
436                   Scan; -- past THEN
437
438                   --  Terminate if THEN ABORT allowed (ATC case)
439
440                   exit when SS_Flags.Tatm and then Token = Tok_Abort;
441
442                   --  Otherwise we treat THEN as some kind of mess where we did
443                   --  not see the associated IF, but we pick up assuming it had
444                   --  been there!
445
446                   Restore_Scan_State (Scan_State); -- to THEN
447                   Append_To (Statement_List, P_If_Statement);
448                   Statement_Required := False;
449
450                --  Case of WHEN (error because we are not in a case)
451
452                when Tok_When | Tok_Others =>
453
454                   --  Terminate if Whtm set or if the WHEN is to the left of
455                   --  the expected column of the end for this sequence.
456
457                   if SS_Flags.Whtm
458                      or else Start_Column < Scope.Table (Scope.Last).Ecol
459                   then
460                      Test_Statement_Required;
461                      exit;
462
463                   --  Otherwise complain and skip when Choice {| Choice} =>
464
465                   else
466                      Error_Msg_SC ("WHEN not allowed here");
467                      Scan; -- past when
468                      Discard_Junk_List (P_Discrete_Choice_List);
469                      TF_Arrow;
470                      Statement_Required := False;
471                   end if;
472
473                --  Cases of statements starting with an identifier
474
475                when Tok_Identifier =>
476                   Check_Bad_Layout;
477
478                   --  Save scan pointers and line number in case block label
479
480                   Id_Node := Token_Node;
481                   Block_Label := Token_Name;
482                   Save_Scan_State (Scan_State_Label); -- at possible label
483                   Scan; -- past Id
484
485                   --  Check for common case of assignment, since it occurs
486                   --  frequently, and we want to process it efficiently.
487
488                   if Token = Tok_Colon_Equal then
489                      Scan; -- past the colon-equal
490                      Append_To (Statement_List,
491                        P_Assignment_Statement (Id_Node));
492                      Statement_Required := False;
493
494                   --  Check common case of procedure call, another case that
495                   --  we want to speed up as much as possible.
496
497                   elsif Token = Tok_Semicolon then
498                      Append_To (Statement_List,
499                        P_Statement_Name (Id_Node));
500                      Scan; -- past semicolon
501                      Statement_Required := False;
502
503                   --  Check for case of "go to" in place of "goto"
504
505                   elsif Token = Tok_Identifier
506                     and then Block_Label = Name_Go
507                     and then Token_Name = Name_To
508                   then
509                      Error_Msg_SP -- CODEFIX
510                        ("goto is one word");
511                      Append_To (Statement_List, P_Goto_Statement);
512                      Statement_Required := False;
513
514                   --  Check common case of = used instead of :=, just so we
515                   --  give a better error message for this special misuse.
516
517                   elsif Token = Tok_Equal then
518                      T_Colon_Equal; -- give := expected message
519                      Append_To (Statement_List,
520                        P_Assignment_Statement (Id_Node));
521                      Statement_Required := False;
522
523                   --  Check case of loop label or block label
524
525                   elsif Token = Tok_Colon
526                     or else (Token in Token_Class_Labeled_Stmt
527                               and then not Token_Is_At_Start_Of_Line)
528                   then
529                      T_Colon; -- past colon (if there, or msg for missing one)
530
531                      --  Test for more than one label
532
533                      loop
534                         exit when Token /= Tok_Identifier;
535                         Save_Scan_State (Scan_State); -- at second Id
536                         Scan; -- past Id
537
538                         if Token = Tok_Colon then
539                            Error_Msg_SP
540                               ("only one label allowed on block or loop");
541                            Scan; -- past colon on extra label
542
543                            --  Use the second label as the "real" label
544
545                            Scan_State_Label := Scan_State;
546
547                            --  We will set Error_name as the Block_Label since
548                            --  we really don't know which of the labels might
549                            --  be used at the end of the loop or block!
550
551                            Block_Label := Error_Name;
552
553                         --  If Id with no colon, then backup to point to the
554                         --  Id and we will issue the message below when we try
555                         --  to scan out the statement as some other form.
556
557                         else
558                            Restore_Scan_State (Scan_State); -- to second Id
559                            exit;
560                         end if;
561                      end loop;
562
563                      --  Loop_Statement (labeled Loop_Statement)
564
565                      if Token = Tok_Loop then
566                         Append_To (Statement_List,
567                           P_Loop_Statement (Id_Node));
568
569                      --  While statement (labeled loop statement with WHILE)
570
571                      elsif Token = Tok_While then
572                         Append_To (Statement_List,
573                           P_While_Statement (Id_Node));
574
575                      --  Declare statement (labeled block statement with
576                      --  DECLARE part)
577
578                      elsif Token = Tok_Declare then
579                         Append_To (Statement_List,
580                           P_Declare_Statement (Id_Node));
581
582                      --  Begin statement (labeled block statement with no
583                      --  DECLARE part)
584
585                      elsif Token = Tok_Begin then
586                         Append_To (Statement_List,
587                           P_Begin_Statement (Id_Node));
588
589                      --  For statement (labeled loop statement with FOR)
590
591                      elsif Token = Tok_For then
592                         Append_To (Statement_List,
593                           P_For_Statement (Id_Node));
594
595                      --  Improper statement follows label. If we have an
596                      --  expression token, then assume the colon was part
597                      --  of a misplaced declaration.
598
599                      elsif Token not in Token_Class_Eterm then
600                         Restore_Scan_State (Scan_State_Label);
601                         Junk_Declaration;
602
603                      --  Otherwise complain we have inappropriate statement
604
605                      else
606                         Error_Msg_AP
607                           ("loop or block statement must follow label");
608                      end if;
609
610                      Statement_Required := False;
611
612                   --  Here we have an identifier followed by something
613                   --  other than a colon, semicolon or assignment symbol.
614                   --  The only valid possibility is a name extension symbol
615
616                   elsif Token in Token_Class_Namext then
617                      Restore_Scan_State (Scan_State_Label); -- to Id
618                      Name_Node := P_Name;
619
620                      --  Skip junk right parens in this context
621
622                      Ignore (Tok_Right_Paren);
623
624                      --  Check context following call
625
626                      if Token = Tok_Colon_Equal then
627                         Scan; -- past colon equal
628                         Append_To (Statement_List,
629                           P_Assignment_Statement (Name_Node));
630                         Statement_Required := False;
631
632                      --  Check common case of = used instead of :=
633
634                      elsif Token = Tok_Equal then
635                         T_Colon_Equal; -- give := expected message
636                         Append_To (Statement_List,
637                           P_Assignment_Statement (Name_Node));
638                         Statement_Required := False;
639
640                      --  Check apostrophe cases
641
642                      elsif Token = Tok_Apostrophe then
643                         Append_To (Statement_List,
644                           P_Code_Statement (Name_Node));
645                         Statement_Required := False;
646
647                      --  The only other valid item after a name is ; which
648                      --  means that the item we just scanned was a call.
649
650                      elsif Token = Tok_Semicolon then
651                         Append_To (Statement_List,
652                           P_Statement_Name (Name_Node));
653                         Scan; -- past semicolon
654                         Statement_Required := False;
655
656                      --  A slash following an identifier or a selected
657                      --  component in this situation is most likely a period
658                      --  (see location of keys on keyboard).
659
660                      elsif Token = Tok_Slash
661                        and then (Nkind (Name_Node) = N_Identifier
662                                    or else
663                                  Nkind (Name_Node) = N_Selected_Component)
664                      then
665                         Error_Msg_SC -- CODEFIX
666                           ("""/"" should be "".""");
667                         Statement_Required := False;
668                         raise Error_Resync;
669
670                      --  Else we have a missing semicolon
671
672                      else
673                         TF_Semicolon;
674                         Statement_Required := False;
675                      end if;
676
677                   --  If junk after identifier, check if identifier is an
678                   --  instance of an incorrectly spelled keyword. If so, we
679                   --  do nothing. The Bad_Spelling_Of will have reset Token
680                   --  to the appropriate keyword, so the next time round the
681                   --  loop we will process the modified token. Note that we
682                   --  check for ELSIF before ELSE here. That's not accidental.
683                   --  We don't want to identify a misspelling of ELSE as
684                   --  ELSIF, and in particular we do not want to treat ELSEIF
685                   --  as ELSE IF.
686
687                   else
688                      Restore_Scan_State (Scan_State_Label); -- to identifier
689
690                      if Bad_Spelling_Of (Tok_Abort)
691                        or else Bad_Spelling_Of (Tok_Accept)
692                        or else Bad_Spelling_Of (Tok_Case)
693                        or else Bad_Spelling_Of (Tok_Declare)
694                        or else Bad_Spelling_Of (Tok_Delay)
695                        or else Bad_Spelling_Of (Tok_Elsif)
696                        or else Bad_Spelling_Of (Tok_Else)
697                        or else Bad_Spelling_Of (Tok_End)
698                        or else Bad_Spelling_Of (Tok_Exception)
699                        or else Bad_Spelling_Of (Tok_Exit)
700                        or else Bad_Spelling_Of (Tok_For)
701                        or else Bad_Spelling_Of (Tok_Goto)
702                        or else Bad_Spelling_Of (Tok_If)
703                        or else Bad_Spelling_Of (Tok_Loop)
704                        or else Bad_Spelling_Of (Tok_Or)
705                        or else Bad_Spelling_Of (Tok_Pragma)
706                        or else Bad_Spelling_Of (Tok_Raise)
707                        or else Bad_Spelling_Of (Tok_Requeue)
708                        or else Bad_Spelling_Of (Tok_Return)
709                        or else Bad_Spelling_Of (Tok_Select)
710                        or else Bad_Spelling_Of (Tok_When)
711                        or else Bad_Spelling_Of (Tok_While)
712                      then
713                         null;
714
715                      --  If not a bad spelling, then we really have junk
716
717                      else
718                         Scan; -- past identifier again
719
720                         --  If next token is first token on line, then we
721                         --  consider that we were missing a semicolon after
722                         --  the identifier, and process it as a procedure
723                         --  call with no parameters.
724
725                         if Token_Is_At_Start_Of_Line then
726                            Append_To (Statement_List,
727                              P_Statement_Name (Id_Node));
728                            T_Semicolon; -- to give error message
729                            Statement_Required := False;
730
731                         --  Otherwise we give a missing := message and
732                         --  simply abandon the junk that is there now.
733
734                         else
735                            T_Colon_Equal; -- give := expected message
736                            raise Error_Resync;
737                         end if;
738
739                      end if;
740                   end if;
741
742                --  Statement starting with operator symbol. This could be
743                --  a call, a name starting an assignment, or a qualified
744                --  expression.
745
746                when Tok_Operator_Symbol =>
747                   Check_Bad_Layout;
748                   Name_Node := P_Name;
749
750                   --  An attempt at a range attribute or a qualified expression
751                   --  must be illegal here (a code statement cannot possibly
752                   --  allow qualification by a function name).
753
754                   if Token = Tok_Apostrophe then
755                      Error_Msg_SC ("apostrophe illegal here");
756                      raise Error_Resync;
757                   end if;
758
759                   --  Scan possible assignment if we have a name
760
761                   if Expr_Form = EF_Name
762                     and then Token = Tok_Colon_Equal
763                   then
764                      Scan; -- past colon equal
765                      Append_To (Statement_List,
766                        P_Assignment_Statement (Name_Node));
767                   else
768                      Append_To (Statement_List,
769                        P_Statement_Name (Name_Node));
770                   end if;
771
772                   TF_Semicolon;
773                   Statement_Required := False;
774
775                --  Label starting with << which must precede real statement
776                --  Note: in Ada2012, the label may end the sequence.
777
778                when Tok_Less_Less =>
779                   if Present (Last (Statement_List))
780                     and then Nkind (Last (Statement_List)) /= N_Label
781                   then
782                      Statement_Seen := True;
783                   end if;
784
785                   Append_To (Statement_List, P_Label);
786                   Statement_Required := True;
787
788                --  Pragma appearing as a statement in a statement sequence
789
790                when Tok_Pragma =>
791                   Check_Bad_Layout;
792                   Append_To (Statement_List, P_Pragma);
793
794                --  Abort_Statement
795
796                when Tok_Abort =>
797                   Check_Bad_Layout;
798                   Append_To (Statement_List, P_Abort_Statement);
799                   Statement_Required := False;
800
801                --  Accept_Statement
802
803                when Tok_Accept =>
804                   Check_Bad_Layout;
805                   Append_To (Statement_List, P_Accept_Statement);
806                   Statement_Required := False;
807
808                --  Begin_Statement (Block_Statement with no declare, no label)
809
810                when Tok_Begin =>
811                   Check_Bad_Layout;
812                   Append_To (Statement_List, P_Begin_Statement);
813                   Statement_Required := False;
814
815                --  Case_Statement
816
817                when Tok_Case =>
818                   Check_Bad_Layout;
819                   Append_To (Statement_List, P_Case_Statement);
820                   Statement_Required := False;
821
822                --  Block_Statement with DECLARE and no label
823
824                when Tok_Declare =>
825                   Check_Bad_Layout;
826                   Append_To (Statement_List, P_Declare_Statement);
827                   Statement_Required := False;
828
829                --  Delay_Statement
830
831                when Tok_Delay =>
832                   Check_Bad_Layout;
833                   Append_To (Statement_List, P_Delay_Statement);
834                   Statement_Required := False;
835
836                --  Exit_Statement
837
838                when Tok_Exit =>
839                   Check_Bad_Layout;
840                   Append_To (Statement_List, P_Exit_Statement);
841                   Statement_Required := False;
842
843                --  Loop_Statement with FOR and no label
844
845                when Tok_For =>
846                   Check_Bad_Layout;
847                   Append_To (Statement_List, P_For_Statement);
848                   Statement_Required := False;
849
850                --  Goto_Statement
851
852                when Tok_Goto =>
853                   Check_Bad_Layout;
854                   Append_To (Statement_List, P_Goto_Statement);
855                   Statement_Required := False;
856
857                --  If_Statement
858
859                when Tok_If =>
860                   Check_Bad_Layout;
861                   Append_To (Statement_List, P_If_Statement);
862                   Statement_Required := False;
863
864                --  Loop_Statement
865
866                when Tok_Loop =>
867                   Check_Bad_Layout;
868                   Append_To (Statement_List, P_Loop_Statement);
869                   Statement_Required := False;
870
871                --  Null_Statement
872
873                when Tok_Null =>
874                   Check_Bad_Layout;
875                   Append_To (Statement_List, P_Null_Statement);
876                   Statement_Required := False;
877
878                --  Raise_Statement
879
880                when Tok_Raise =>
881                   Check_Bad_Layout;
882                   Append_To (Statement_List, P_Raise_Statement);
883                   Statement_Required := False;
884
885                --  Requeue_Statement
886
887                when Tok_Requeue =>
888                   Check_Bad_Layout;
889                   Append_To (Statement_List, P_Requeue_Statement);
890                   Statement_Required := False;
891
892                --  Return_Statement
893
894                when Tok_Return =>
895                   Check_Bad_Layout;
896                   Append_To (Statement_List, P_Return_Statement);
897                   Statement_Required := False;
898
899                --  Select_Statement
900
901                when Tok_Select =>
902                   Check_Bad_Layout;
903                   Append_To (Statement_List, P_Select_Statement);
904                   Statement_Required := False;
905
906                --  While_Statement (Block_Statement with while and no loop)
907
908                when Tok_While =>
909                   Check_Bad_Layout;
910                   Append_To (Statement_List, P_While_Statement);
911                   Statement_Required := False;
912
913                --  Anything else is some kind of junk, signal an error message
914                --  and then raise Error_Resync, to merge with the normal
915                --  handling of a bad statement.
916
917                when others =>
918
919                   if Token in Token_Class_Declk then
920                      Junk_Declaration;
921
922                   else
923                      Error_Msg_BC -- CODEFIX
924                        ("statement expected");
925                      raise Error_Resync;
926                   end if;
927             end case;
928
929          --  On error resynchronization, skip past next semicolon, and, since
930          --  we are still in the statement loop, look for next statement. We
931          --  set Statement_Required False to avoid an unnecessary error message
932          --  complaining that no statement was found (i.e. we consider the
933          --  junk to satisfy the requirement for a statement being present).
934
935          exception
936             when Error_Resync =>
937                Resync_Past_Semicolon_Or_To_Loop_Or_Then;
938                Statement_Required := False;
939          end;
940
941          exit when SS_Flags.Unco;
942
943       end loop;
944
945       return Statement_List;
946
947    end P_Sequence_Of_Statements;
948
949    --------------------
950    -- 5.1  Statement --
951    --------------------
952
953    --  Parsed by P_Sequence_Of_Statements (5.1), except for the case
954    --  of a statement of the form of a name, which is handled here. The
955    --  argument passed in is the tree for the name which has been scanned
956    --  The returned value is the corresponding statement form.
957
958    --  This routine is also used by Par.Prag for processing the procedure
959    --  call that appears as the second argument of a pragma Assert.
960
961    --  Error recovery: cannot raise Error_Resync
962
963    function P_Statement_Name (Name_Node : Node_Id) return Node_Id is
964       Stmt_Node : Node_Id;
965
966    begin
967       --  Case of Indexed component, which is a procedure call with arguments
968
969       if Nkind (Name_Node) = N_Indexed_Component then
970          declare
971             Prefix_Node : constant Node_Id := Prefix (Name_Node);
972             Exprs_Node  : constant List_Id := Expressions (Name_Node);
973
974          begin
975             Change_Node (Name_Node, N_Procedure_Call_Statement);
976             Set_Name (Name_Node, Prefix_Node);
977             Set_Parameter_Associations (Name_Node, Exprs_Node);
978             return Name_Node;
979          end;
980
981       --  Case of function call node, which is a really a procedure call
982
983       elsif Nkind (Name_Node) = N_Function_Call then
984          declare
985             Fname_Node  : constant Node_Id := Name (Name_Node);
986             Params_List : constant List_Id :=
987                             Parameter_Associations (Name_Node);
988
989          begin
990             Change_Node (Name_Node, N_Procedure_Call_Statement);
991             Set_Name (Name_Node, Fname_Node);
992             Set_Parameter_Associations (Name_Node, Params_List);
993             return Name_Node;
994          end;
995
996       --  Case of call to attribute that denotes a procedure. Here we
997       --  just leave the attribute reference unchanged.
998
999       elsif Nkind (Name_Node) = N_Attribute_Reference
1000         and then Is_Procedure_Attribute_Name (Attribute_Name (Name_Node))
1001       then
1002          return Name_Node;
1003
1004       --  All other cases of names are parameterless procedure calls
1005
1006       else
1007          Stmt_Node :=
1008            New_Node (N_Procedure_Call_Statement, Sloc (Name_Node));
1009          Set_Name (Stmt_Node, Name_Node);
1010          return Stmt_Node;
1011       end if;
1012
1013    end P_Statement_Name;
1014
1015    ---------------------------
1016    -- 5.1  Simple Statement --
1017    ---------------------------
1018
1019    --  Parsed by P_Sequence_Of_Statements (5.1)
1020
1021    -----------------------------
1022    -- 5.1  Compound Statement --
1023    -----------------------------
1024
1025    --  Parsed by P_Sequence_Of_Statements (5.1)
1026
1027    -------------------------
1028    -- 5.1  Null Statement --
1029    -------------------------
1030
1031    --  NULL_STATEMENT ::= null;
1032
1033    --  The caller has already checked that the current token is null
1034
1035    --  Error recovery: cannot raise Error_Resync
1036
1037    function P_Null_Statement return Node_Id is
1038       Null_Stmt_Node : Node_Id;
1039
1040    begin
1041       Null_Stmt_Node := New_Node (N_Null_Statement, Token_Ptr);
1042       Scan; -- past NULL
1043       TF_Semicolon;
1044       return Null_Stmt_Node;
1045    end P_Null_Statement;
1046
1047    ----------------
1048    -- 5.1  Label --
1049    ----------------
1050
1051    --  LABEL ::= <<label_STATEMENT_IDENTIFIER>>
1052
1053    --  STATEMENT_IDENTIFIER ::= DIRECT_NAME
1054
1055    --  The IDENTIFIER of a STATEMENT_IDENTIFIER shall be an identifier
1056    --  (not an OPERATOR_SYMBOL)
1057
1058    --  The caller has already checked that the current token is <<
1059
1060    --  Error recovery: can raise Error_Resync
1061
1062    function P_Label return Node_Id is
1063       Label_Node : Node_Id;
1064
1065    begin
1066       Label_Node := New_Node (N_Label, Token_Ptr);
1067       Scan; -- past <<
1068       Set_Identifier (Label_Node, P_Identifier (C_Greater_Greater));
1069       T_Greater_Greater;
1070       Append_Elmt (Label_Node, Label_List);
1071       return Label_Node;
1072    end P_Label;
1073
1074    -------------------------------
1075    -- 5.1  Statement Identifier --
1076    -------------------------------
1077
1078    --  Statement label is parsed by P_Label (5.1)
1079
1080    --  Loop label is parsed by P_Loop_Statement (5.5), P_For_Statement (5.5)
1081    --   or P_While_Statement (5.5)
1082
1083    --  Block label is parsed by P_Begin_Statement (5.6) or
1084    --   P_Declare_Statement (5.6)
1085
1086    -------------------------------
1087    -- 5.2  Assignment Statement --
1088    -------------------------------
1089
1090    --  ASSIGNMENT_STATEMENT ::=
1091    --    variable_NAME := EXPRESSION;
1092
1093    --  Error recovery: can raise Error_Resync
1094
1095    function P_Assignment_Statement (LHS : Node_Id) return Node_Id is
1096       Assign_Node : Node_Id;
1097
1098    begin
1099       Assign_Node := New_Node (N_Assignment_Statement, Prev_Token_Ptr);
1100       Set_Name (Assign_Node, LHS);
1101       Set_Expression (Assign_Node, P_Expression_No_Right_Paren);
1102       TF_Semicolon;
1103       return Assign_Node;
1104    end P_Assignment_Statement;
1105
1106    -----------------------
1107    -- 5.3  If Statement --
1108    -----------------------
1109
1110    --  IF_STATEMENT ::=
1111    --    if CONDITION then
1112    --      SEQUENCE_OF_STATEMENTS
1113    --    {elsif CONDITION then
1114    --      SEQUENCE_OF_STATEMENTS}
1115    --    [else
1116    --      SEQUENCE_OF_STATEMENTS]
1117    --    end if;
1118
1119    --  The caller has checked that the initial token is IF (or in the error
1120    --  case of a mysterious THEN, the initial token may simply be THEN, in
1121    --  which case, no condition (or IF) was scanned).
1122
1123    --  Error recovery: can raise Error_Resync
1124
1125    function P_If_Statement return Node_Id is
1126       If_Node    : Node_Id;
1127       Elsif_Node : Node_Id;
1128       Loc        : Source_Ptr;
1129
1130       procedure Add_Elsif_Part;
1131       --  An internal procedure used to scan out a single ELSIF part. On entry
1132       --  the ELSIF (or an ELSE which has been determined should be ELSIF) is
1133       --  scanned out and is in Prev_Token.
1134
1135       procedure Check_If_Column;
1136       --  An internal procedure used to check that THEN, ELSE, or ELSIF
1137       --  appear in the right place if column checking is enabled (i.e. if
1138       --  they are the first token on the line, then they must appear in
1139       --  the same column as the opening IF).
1140
1141       procedure Check_Then_Column;
1142       --  This procedure carries out the style checks for a THEN token
1143       --  Note that the caller has set Loc to the Source_Ptr value for
1144       --  the previous IF or ELSIF token. These checks apply only to a
1145       --  THEN at the start of a line.
1146
1147       function Else_Should_Be_Elsif return Boolean;
1148       --  An internal routine used to do a special error recovery check when
1149       --  an ELSE is encountered. It determines if the ELSE should be treated
1150       --  as an ELSIF. A positive decision (TRUE returned, is made if the ELSE
1151       --  is followed by a sequence of tokens, starting on the same line as
1152       --  the ELSE, which are not expression terminators, followed by a THEN.
1153       --  On entry, the ELSE has been scanned out.
1154
1155       procedure Add_Elsif_Part is
1156       begin
1157          if No (Elsif_Parts (If_Node)) then
1158             Set_Elsif_Parts (If_Node, New_List);
1159          end if;
1160
1161          Elsif_Node := New_Node (N_Elsif_Part, Prev_Token_Ptr);
1162          Loc := Prev_Token_Ptr;
1163          Set_Condition (Elsif_Node, P_Condition);
1164          Check_Then_Column;
1165          Then_Scan;
1166          Set_Then_Statements
1167            (Elsif_Node, P_Sequence_Of_Statements (SS_Eftm_Eltm_Sreq));
1168          Append (Elsif_Node, Elsif_Parts (If_Node));
1169       end Add_Elsif_Part;
1170
1171       procedure Check_If_Column is
1172       begin
1173          if RM_Column_Check and then Token_Is_At_Start_Of_Line
1174            and then Start_Column /= Scope.Table (Scope.Last).Ecol
1175          then
1176             Error_Msg_Col := Scope.Table (Scope.Last).Ecol;
1177             Error_Msg_SC ("(style) this token should be@");
1178          end if;
1179       end Check_If_Column;
1180
1181       procedure Check_Then_Column is
1182       begin
1183          if Token_Is_At_Start_Of_Line and then Token = Tok_Then then
1184             Check_If_Column;
1185
1186             if Style_Check then
1187                Style.Check_Then (Loc);
1188             end if;
1189          end if;
1190       end Check_Then_Column;
1191
1192       function Else_Should_Be_Elsif return Boolean is
1193          Scan_State : Saved_Scan_State;
1194
1195       begin
1196          if Token_Is_At_Start_Of_Line then
1197             return False;
1198
1199          else
1200             Save_Scan_State (Scan_State);
1201
1202             loop
1203                if Token in Token_Class_Eterm then
1204                   Restore_Scan_State (Scan_State);
1205                   return False;
1206                else
1207                   Scan; -- past non-expression terminating token
1208
1209                   if Token = Tok_Then then
1210                      Restore_Scan_State (Scan_State);
1211                      return True;
1212                   end if;
1213                end if;
1214             end loop;
1215          end if;
1216       end Else_Should_Be_Elsif;
1217
1218    --  Start of processing for P_If_Statement
1219
1220    begin
1221       If_Node := New_Node (N_If_Statement, Token_Ptr);
1222
1223       Push_Scope_Stack;
1224       Scope.Table (Scope.Last).Etyp := E_If;
1225       Scope.Table (Scope.Last).Ecol := Start_Column;
1226       Scope.Table (Scope.Last).Sloc := Token_Ptr;
1227       Scope.Table (Scope.Last).Labl := Error;
1228       Scope.Table (Scope.Last).Node := If_Node;
1229
1230       if Token = Tok_If then
1231          Loc := Token_Ptr;
1232          Scan; -- past IF
1233          Set_Condition (If_Node, P_Condition);
1234
1235          --  Deal with misuse of IF expression => used instead
1236          --  of WHEN expression =>
1237
1238          if Token = Tok_Arrow then
1239             Error_Msg_SC -- CODEFIX
1240               ("THEN expected");
1241             Scan; -- past the arrow
1242             Pop_Scope_Stack; -- remove unneeded entry
1243             raise Error_Resync;
1244          end if;
1245
1246          Check_Then_Column;
1247
1248       else
1249          Error_Msg_SC ("no IF for this THEN");
1250          Set_Condition (If_Node, Error);
1251       end if;
1252
1253       Then_Scan;
1254
1255       Set_Then_Statements
1256         (If_Node, P_Sequence_Of_Statements (SS_Eftm_Eltm_Sreq));
1257
1258       --  This loop scans out else and elsif parts
1259
1260       loop
1261          if Token = Tok_Elsif then
1262             Check_If_Column;
1263
1264             if Present (Else_Statements (If_Node)) then
1265                Error_Msg_SP ("ELSIF cannot appear after ELSE");
1266             end if;
1267
1268             Scan; -- past ELSIF
1269             Add_Elsif_Part;
1270
1271          elsif Token = Tok_Else then
1272             Check_If_Column;
1273             Scan; -- past ELSE
1274
1275             if Else_Should_Be_Elsif then
1276                Error_Msg_SP -- CODEFIX
1277                  ("ELSE should be ELSIF");
1278                Add_Elsif_Part;
1279
1280             else
1281                --  Here we have an else that really is an else
1282
1283                if Present (Else_Statements (If_Node)) then
1284                   Error_Msg_SP ("only one ELSE part allowed");
1285                   Append_List
1286                     (P_Sequence_Of_Statements (SS_Eftm_Eltm_Sreq),
1287                      Else_Statements (If_Node));
1288                else
1289                   Set_Else_Statements
1290                     (If_Node, P_Sequence_Of_Statements (SS_Eftm_Eltm_Sreq));
1291                end if;
1292             end if;
1293
1294          --  If anything other than ELSE or ELSIF, exit the loop. The token
1295          --  had better be END (and in fact it had better be END IF), but
1296          --  we will let End_Statements take care of checking that.
1297
1298          else
1299             exit;
1300          end if;
1301       end loop;
1302
1303       End_Statements;
1304       return If_Node;
1305
1306    end P_If_Statement;
1307
1308    --------------------
1309    -- 5.3  Condition --
1310    --------------------
1311
1312    --  CONDITION ::= boolean_EXPRESSION
1313
1314    function P_Condition return Node_Id is
1315       Cond : Node_Id;
1316
1317    begin
1318       Cond := P_Expression_No_Right_Paren;
1319
1320       --  It is never possible for := to follow a condition, so if we get
1321       --  a := we assume it is a mistyped equality. Note that we do not try
1322       --  to reconstruct the tree correctly in this case, but we do at least
1323       --  give an accurate error message.
1324
1325       if Token = Tok_Colon_Equal then
1326          while Token = Tok_Colon_Equal loop
1327             Error_Msg_SC -- CODEFIX
1328               (""":="" should be ""=""");
1329             Scan; -- past junk :=
1330             Discard_Junk_Node (P_Expression_No_Right_Paren);
1331          end loop;
1332
1333          return Cond;
1334
1335       --  Otherwise check for redundant parens
1336
1337       else
1338          if Style_Check
1339            and then Paren_Count (Cond) > 0
1340          then
1341             Style.Check_Xtra_Parens (First_Sloc (Cond));
1342          end if;
1343
1344          --  And return the result
1345
1346          return Cond;
1347       end if;
1348    end P_Condition;
1349
1350    -------------------------
1351    -- 5.4  Case Statement --
1352    -------------------------
1353
1354    --  CASE_STATEMENT ::=
1355    --    case EXPRESSION is
1356    --      CASE_STATEMENT_ALTERNATIVE
1357    --      {CASE_STATEMENT_ALTERNATIVE}
1358    --    end case;
1359
1360    --  The caller has checked that the first token is CASE
1361
1362    --  Can raise Error_Resync
1363
1364    function P_Case_Statement return Node_Id is
1365       Case_Node         : Node_Id;
1366       Alternatives_List : List_Id;
1367       First_When_Loc    : Source_Ptr;
1368
1369    begin
1370       Case_Node := New_Node (N_Case_Statement, Token_Ptr);
1371
1372       Push_Scope_Stack;
1373       Scope.Table (Scope.Last).Etyp := E_Case;
1374       Scope.Table (Scope.Last).Ecol := Start_Column;
1375       Scope.Table (Scope.Last).Sloc := Token_Ptr;
1376       Scope.Table (Scope.Last).Labl := Error;
1377       Scope.Table (Scope.Last).Node := Case_Node;
1378
1379       Scan; -- past CASE
1380       Set_Expression (Case_Node, P_Expression_No_Right_Paren);
1381       TF_Is;
1382
1383       --  Prepare to parse case statement alternatives
1384
1385       Alternatives_List := New_List;
1386       P_Pragmas_Opt (Alternatives_List);
1387       First_When_Loc := Token_Ptr;
1388
1389       --  Loop through case statement alternatives
1390
1391       loop
1392          --  If we have a WHEN or OTHERS, then that's fine keep going. Note
1393          --  that it is a semantic check to ensure the proper use of OTHERS
1394
1395          if Token = Tok_When or else Token = Tok_Others then
1396             Append (P_Case_Statement_Alternative, Alternatives_List);
1397
1398          --  If we have an END, then probably we are at the end of the case
1399          --  but we only exit if Check_End thinks the END was reasonable.
1400
1401          elsif Token = Tok_End then
1402             exit when Check_End;
1403
1404          --  Here if token is other than WHEN, OTHERS or END. We definitely
1405          --  have an error, but the question is whether or not to get out of
1406          --  the case statement. We don't want to get out early, or we will
1407          --  get a slew of junk error messages for subsequent when tokens.
1408
1409          --  If the token is not at the start of the line, or if it is indented
1410          --  with respect to the current case statement, then the best guess is
1411          --  that we are still supposed to be inside the case statement. We
1412          --  complain about the missing WHEN, and discard the junk statements.
1413
1414          elsif not Token_Is_At_Start_Of_Line
1415            or else Start_Column > Scope.Table (Scope.Last).Ecol
1416          then
1417             Error_Msg_BC ("WHEN (case statement alternative) expected");
1418
1419             --  Here is a possibility for infinite looping if we don't make
1420             --  progress. So try to process statements, otherwise exit
1421
1422             declare
1423                Error_Ptr : constant Source_Ptr := Scan_Ptr;
1424             begin
1425                Discard_Junk_List (P_Sequence_Of_Statements (SS_Whtm));
1426                exit when Scan_Ptr = Error_Ptr and then Check_End;
1427             end;
1428
1429          --  Here we have a junk token at the start of the line and it is
1430          --  not indented. If Check_End thinks there is a missing END, then
1431          --  we will get out of the case, otherwise we keep going.
1432
1433          else
1434             exit when Check_End;
1435          end if;
1436       end loop;
1437
1438       --  Make sure we have at least one alternative
1439
1440       if No (First_Non_Pragma (Alternatives_List)) then
1441          Error_Msg
1442             ("WHEN expected, must have at least one alternative in case",
1443              First_When_Loc);
1444          return Error;
1445
1446       else
1447          Set_Alternatives (Case_Node, Alternatives_List);
1448          return Case_Node;
1449       end if;
1450    end P_Case_Statement;
1451
1452    -------------------------------------
1453    -- 5.4  Case Statement Alternative --
1454    -------------------------------------
1455
1456    --  CASE_STATEMENT_ALTERNATIVE ::=
1457    --    when DISCRETE_CHOICE_LIST =>
1458    --      SEQUENCE_OF_STATEMENTS
1459
1460    --  The caller has checked that the initial token is WHEN or OTHERS
1461    --  Error recovery: can raise Error_Resync
1462
1463    function P_Case_Statement_Alternative return Node_Id is
1464       Case_Alt_Node : Node_Id;
1465
1466    begin
1467       if Style_Check then
1468          Style.Check_Indentation;
1469       end if;
1470
1471       Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Token_Ptr);
1472       T_When; -- past WHEN (or give error in OTHERS case)
1473       Set_Discrete_Choices (Case_Alt_Node, P_Discrete_Choice_List);
1474       TF_Arrow;
1475       Set_Statements (Case_Alt_Node, P_Sequence_Of_Statements (SS_Sreq_Whtm));
1476       return Case_Alt_Node;
1477    end P_Case_Statement_Alternative;
1478
1479    -------------------------
1480    -- 5.5  Loop Statement --
1481    -------------------------
1482
1483    --  LOOP_STATEMENT ::=
1484    --    [LOOP_STATEMENT_IDENTIFIER:]
1485    --      [ITERATION_SCHEME] loop
1486    --        SEQUENCE_OF_STATEMENTS
1487    --      end loop [loop_IDENTIFIER];
1488
1489    --  ITERATION_SCHEME ::=
1490    --    while CONDITION
1491    --  | for LOOP_PARAMETER_SPECIFICATION
1492
1493    --  The parsing of loop statements is handled by one of three functions
1494    --  P_Loop_Statement, P_For_Statement or P_While_Statement depending
1495    --  on the initial keyword in the construct (excluding the identifier)
1496
1497    --  P_Loop_Statement
1498
1499    --  This function parses the case where no iteration scheme is present
1500
1501    --  The caller has checked that the initial token is LOOP. The parameter
1502    --  is the node identifiers for the loop label if any (or is set to Empty
1503    --  if there is no loop label).
1504
1505    --  Error recovery : cannot raise Error_Resync
1506
1507    function P_Loop_Statement (Loop_Name : Node_Id := Empty) return Node_Id is
1508       Loop_Node    : Node_Id;
1509       Created_Name : Node_Id;
1510
1511    begin
1512       Push_Scope_Stack;
1513       Scope.Table (Scope.Last).Labl := Loop_Name;
1514       Scope.Table (Scope.Last).Ecol := Start_Column;
1515       Scope.Table (Scope.Last).Sloc := Token_Ptr;
1516       Scope.Table (Scope.Last).Etyp := E_Loop;
1517
1518       Loop_Node := New_Node (N_Loop_Statement, Token_Ptr);
1519       TF_Loop;
1520
1521       if No (Loop_Name) then
1522          Created_Name :=
1523            Make_Identifier (Sloc (Loop_Node),
1524              Chars => Set_Loop_Block_Name ('L'));
1525          Set_Comes_From_Source (Created_Name, False);
1526          Set_Has_Created_Identifier (Loop_Node, True);
1527          Set_Identifier (Loop_Node, Created_Name);
1528          Scope.Table (Scope.Last).Labl := Created_Name;
1529       else
1530          Set_Identifier (Loop_Node, Loop_Name);
1531       end if;
1532
1533       Append_Elmt (Loop_Node, Label_List);
1534       Set_Statements (Loop_Node, P_Sequence_Of_Statements (SS_Sreq));
1535       End_Statements (Loop_Node);
1536       return Loop_Node;
1537    end P_Loop_Statement;
1538
1539    --  P_For_Statement
1540
1541    --  This function parses a loop statement with a FOR iteration scheme
1542
1543    --  The caller has checked that the initial token is FOR. The parameter
1544    --  is the node identifier for the block label if any (or is set to Empty
1545    --  if there is no block label).
1546
1547    --  Note: the caller fills in the Identifier field if a label was present
1548
1549    --  Error recovery: can raise Error_Resync
1550
1551    function P_For_Statement (Loop_Name : Node_Id := Empty) return Node_Id is
1552       Loop_Node        : Node_Id;
1553       Iter_Scheme_Node : Node_Id;
1554       Loop_For_Flag    : Boolean;
1555       Created_Name     : Node_Id;
1556
1557    begin
1558       Push_Scope_Stack;
1559       Scope.Table (Scope.Last).Labl := Loop_Name;
1560       Scope.Table (Scope.Last).Ecol := Start_Column;
1561       Scope.Table (Scope.Last).Sloc := Token_Ptr;
1562       Scope.Table (Scope.Last).Etyp := E_Loop;
1563
1564       Loop_For_Flag := (Prev_Token = Tok_Loop);
1565       Scan; -- past FOR
1566       Iter_Scheme_Node := New_Node (N_Iteration_Scheme, Token_Ptr);
1567       Set_Loop_Parameter_Specification
1568          (Iter_Scheme_Node, P_Loop_Parameter_Specification);
1569
1570       --  The following is a special test so that a miswritten for loop such
1571       --  as "loop for I in 1..10;" is handled nicely, without making an extra
1572       --  entry in the scope stack. We don't bother to actually fix up the
1573       --  tree in this case since it's not worth the effort. Instead we just
1574       --  eat up the loop junk, leaving the entry for what now looks like an
1575       --  unmodified loop intact.
1576
1577       if Loop_For_Flag and then Token = Tok_Semicolon then
1578          Error_Msg_SC ("LOOP belongs here, not before FOR");
1579          Pop_Scope_Stack;
1580          return Error;
1581
1582       --  Normal case
1583
1584       else
1585          Loop_Node := New_Node (N_Loop_Statement, Token_Ptr);
1586
1587          if No (Loop_Name) then
1588             Created_Name :=
1589               Make_Identifier (Sloc (Loop_Node),
1590                 Chars => Set_Loop_Block_Name ('L'));
1591             Set_Comes_From_Source (Created_Name, False);
1592             Set_Has_Created_Identifier (Loop_Node, True);
1593             Set_Identifier (Loop_Node, Created_Name);
1594             Scope.Table (Scope.Last).Labl := Created_Name;
1595          else
1596             Set_Identifier (Loop_Node, Loop_Name);
1597          end if;
1598
1599          TF_Loop;
1600          Set_Statements (Loop_Node, P_Sequence_Of_Statements (SS_Sreq));
1601          End_Statements (Loop_Node);
1602          Set_Iteration_Scheme (Loop_Node, Iter_Scheme_Node);
1603          Append_Elmt (Loop_Node, Label_List);
1604          return Loop_Node;
1605       end if;
1606    end P_For_Statement;
1607
1608    --  P_While_Statement
1609
1610    --  This procedure scans a loop statement with a WHILE iteration scheme
1611
1612    --  The caller has checked that the initial token is WHILE. The parameter
1613    --  is the node identifier for the block label if any (or is set to Empty
1614    --  if there is no block label).
1615
1616    --  Error recovery: cannot raise Error_Resync
1617
1618    function P_While_Statement (Loop_Name : Node_Id := Empty) return Node_Id is
1619       Loop_Node        : Node_Id;
1620       Iter_Scheme_Node : Node_Id;
1621       Loop_While_Flag  : Boolean;
1622       Created_Name     : Node_Id;
1623
1624    begin
1625       Push_Scope_Stack;
1626       Scope.Table (Scope.Last).Labl := Loop_Name;
1627       Scope.Table (Scope.Last).Ecol := Start_Column;
1628       Scope.Table (Scope.Last).Sloc := Token_Ptr;
1629       Scope.Table (Scope.Last).Etyp := E_Loop;
1630
1631       Loop_While_Flag := (Prev_Token = Tok_Loop);
1632       Iter_Scheme_Node := New_Node (N_Iteration_Scheme, Token_Ptr);
1633       Scan; -- past WHILE
1634       Set_Condition (Iter_Scheme_Node, P_Condition);
1635
1636       --  The following is a special test so that a miswritten for loop such
1637       --  as "loop while I > 10;" is handled nicely, without making an extra
1638       --  entry in the scope stack. We don't bother to actually fix up the
1639       --  tree in this case since it's not worth the effort. Instead we just
1640       --  eat up the loop junk, leaving the entry for what now looks like an
1641       --  unmodified loop intact.
1642
1643       if Loop_While_Flag and then Token = Tok_Semicolon then
1644          Error_Msg_SC ("LOOP belongs here, not before WHILE");
1645          Pop_Scope_Stack;
1646          return Error;
1647
1648       --  Normal case
1649
1650       else
1651          Loop_Node := New_Node (N_Loop_Statement, Token_Ptr);
1652          TF_Loop;
1653
1654          if No (Loop_Name) then
1655             Created_Name :=
1656               Make_Identifier (Sloc (Loop_Node),
1657                 Chars => Set_Loop_Block_Name ('L'));
1658             Set_Comes_From_Source (Created_Name, False);
1659             Set_Has_Created_Identifier (Loop_Node, True);
1660             Set_Identifier (Loop_Node, Created_Name);
1661             Scope.Table (Scope.Last).Labl := Created_Name;
1662          else
1663             Set_Identifier (Loop_Node, Loop_Name);
1664          end if;
1665
1666          Set_Statements (Loop_Node, P_Sequence_Of_Statements (SS_Sreq));
1667          End_Statements (Loop_Node);
1668          Set_Iteration_Scheme (Loop_Node, Iter_Scheme_Node);
1669          Append_Elmt (Loop_Node, Label_List);
1670          return Loop_Node;
1671       end if;
1672    end P_While_Statement;
1673
1674    ---------------------------------------
1675    -- 5.5  Loop Parameter Specification --
1676    ---------------------------------------
1677
1678    --  LOOP_PARAMETER_SPECIFICATION ::=
1679    --    DEFINING_IDENTIFIER in [reverse] DISCRETE_SUBTYPE_DEFINITION
1680
1681    --  Error recovery: cannot raise Error_Resync
1682
1683    function P_Loop_Parameter_Specification return Node_Id is
1684       Loop_Param_Specification_Node : Node_Id;
1685
1686       ID_Node    : Node_Id;
1687       Scan_State : Saved_Scan_State;
1688
1689    begin
1690       Loop_Param_Specification_Node :=
1691         New_Node (N_Loop_Parameter_Specification, Token_Ptr);
1692
1693       Save_Scan_State (Scan_State);
1694       ID_Node := P_Defining_Identifier (C_In);
1695       Set_Defining_Identifier (Loop_Param_Specification_Node, ID_Node);
1696
1697       if Token = Tok_Left_Paren then
1698          Error_Msg_SC ("subscripted loop parameter not allowed");
1699          Restore_Scan_State (Scan_State);
1700          Discard_Junk_Node (P_Name);
1701
1702       elsif Token = Tok_Dot then
1703          Error_Msg_SC ("selected loop parameter not allowed");
1704          Restore_Scan_State (Scan_State);
1705          Discard_Junk_Node (P_Name);
1706       end if;
1707
1708       T_In;
1709
1710       if Token = Tok_Reverse then
1711          Scan; -- past REVERSE
1712          Set_Reverse_Present (Loop_Param_Specification_Node, True);
1713       end if;
1714
1715       Set_Discrete_Subtype_Definition
1716         (Loop_Param_Specification_Node, P_Discrete_Subtype_Definition);
1717       return Loop_Param_Specification_Node;
1718
1719    exception
1720       when Error_Resync =>
1721          return Error;
1722    end P_Loop_Parameter_Specification;
1723
1724    --------------------------
1725    -- 5.6  Block Statement --
1726    --------------------------
1727
1728    --  BLOCK_STATEMENT ::=
1729    --    [block_STATEMENT_IDENTIFIER:]
1730    --      [declare
1731    --        DECLARATIVE_PART]
1732    --      begin
1733    --        HANDLED_SEQUENCE_OF_STATEMENTS
1734    --      end [block_IDENTIFIER];
1735
1736    --  The parsing of block statements is handled by one of the two functions
1737    --  P_Declare_Statement or P_Begin_Statement depending on whether or not
1738    --  a declare section is present
1739
1740    --  P_Declare_Statement
1741
1742    --  This function parses a block statement with DECLARE present
1743
1744    --  The caller has checked that the initial token is DECLARE
1745
1746    --  Error recovery: cannot raise Error_Resync
1747
1748    function P_Declare_Statement
1749      (Block_Name : Node_Id := Empty)
1750       return       Node_Id
1751    is
1752       Block_Node   : Node_Id;
1753       Created_Name : Node_Id;
1754
1755    begin
1756       Block_Node := New_Node (N_Block_Statement, Token_Ptr);
1757
1758       Push_Scope_Stack;
1759       Scope.Table (Scope.Last).Etyp := E_Name;
1760       Scope.Table (Scope.Last).Lreq := Present (Block_Name);
1761       Scope.Table (Scope.Last).Ecol := Start_Column;
1762       Scope.Table (Scope.Last).Labl := Block_Name;
1763       Scope.Table (Scope.Last).Sloc := Token_Ptr;
1764
1765       Scan; -- past DECLARE
1766
1767       if No (Block_Name) then
1768          Created_Name :=
1769            Make_Identifier (Sloc (Block_Node),
1770              Chars => Set_Loop_Block_Name ('B'));
1771          Set_Comes_From_Source (Created_Name, False);
1772          Set_Has_Created_Identifier (Block_Node, True);
1773          Set_Identifier (Block_Node, Created_Name);
1774          Scope.Table (Scope.Last).Labl := Created_Name;
1775       else
1776          Set_Identifier (Block_Node, Block_Name);
1777       end if;
1778
1779       Append_Elmt (Block_Node, Label_List);
1780       Parse_Decls_Begin_End (Block_Node);
1781       return Block_Node;
1782    end P_Declare_Statement;
1783
1784    --  P_Begin_Statement
1785
1786    --  This function parses a block statement with no DECLARE present
1787
1788    --  The caller has checked that the initial token is BEGIN
1789
1790    --  Error recovery: cannot raise Error_Resync
1791
1792    function P_Begin_Statement
1793      (Block_Name : Node_Id := Empty)
1794       return       Node_Id
1795    is
1796       Block_Node   : Node_Id;
1797       Created_Name : Node_Id;
1798
1799    begin
1800       Block_Node := New_Node (N_Block_Statement, Token_Ptr);
1801
1802       Push_Scope_Stack;
1803       Scope.Table (Scope.Last).Etyp := E_Name;
1804       Scope.Table (Scope.Last).Lreq := Present (Block_Name);
1805       Scope.Table (Scope.Last).Ecol := Start_Column;
1806       Scope.Table (Scope.Last).Labl := Block_Name;
1807       Scope.Table (Scope.Last).Sloc := Token_Ptr;
1808
1809       if No (Block_Name) then
1810          Created_Name :=
1811            Make_Identifier (Sloc (Block_Node),
1812              Chars => Set_Loop_Block_Name ('B'));
1813          Set_Comes_From_Source (Created_Name, False);
1814          Set_Has_Created_Identifier (Block_Node, True);
1815          Set_Identifier (Block_Node, Created_Name);
1816          Scope.Table (Scope.Last).Labl := Created_Name;
1817       else
1818          Set_Identifier (Block_Node, Block_Name);
1819       end if;
1820
1821       Append_Elmt (Block_Node, Label_List);
1822
1823       Scope.Table (Scope.Last).Ecol := Start_Column;
1824       Scope.Table (Scope.Last).Sloc := Token_Ptr;
1825       Scan; -- past BEGIN
1826       Set_Handled_Statement_Sequence
1827         (Block_Node, P_Handled_Sequence_Of_Statements);
1828       End_Statements (Handled_Statement_Sequence (Block_Node));
1829       return Block_Node;
1830    end P_Begin_Statement;
1831
1832    -------------------------
1833    -- 5.7  Exit Statement --
1834    -------------------------
1835
1836    --  EXIT_STATEMENT ::=
1837    --    exit [loop_NAME] [when CONDITION];
1838
1839    --  The caller has checked that the initial token is EXIT
1840
1841    --  Error recovery: can raise Error_Resync
1842
1843    function P_Exit_Statement return Node_Id is
1844       Exit_Node : Node_Id;
1845
1846       function Missing_Semicolon_On_Exit return Boolean;
1847       --  This function deals with the following specialized situation
1848       --
1849       --    when 'x' =>
1850       --       exit [identifier]
1851       --    when 'y' =>
1852       --
1853       --  This looks like a messed up EXIT WHEN, when in fact the problem
1854       --  is a missing semicolon. It is called with Token pointing to the
1855       --  WHEN token, and returns True if a semicolon is missing before
1856       --  the WHEN as in the above example.
1857
1858       -------------------------------
1859       -- Missing_Semicolon_On_Exit --
1860       -------------------------------
1861
1862       function Missing_Semicolon_On_Exit return Boolean is
1863          State : Saved_Scan_State;
1864
1865       begin
1866          if not Token_Is_At_Start_Of_Line then
1867             return False;
1868
1869          elsif Scope.Table (Scope.Last).Etyp /= E_Case then
1870             return False;
1871
1872          else
1873             Save_Scan_State (State);
1874             Scan; -- past WHEN
1875             Scan; -- past token after WHEN
1876
1877             if Token = Tok_Arrow then
1878                Restore_Scan_State (State);
1879                return True;
1880             else
1881                Restore_Scan_State (State);
1882                return False;
1883             end if;
1884          end if;
1885       end Missing_Semicolon_On_Exit;
1886
1887    --  Start of processing for P_Exit_Statement
1888
1889    begin
1890       Exit_Node := New_Node (N_Exit_Statement, Token_Ptr);
1891       Scan; -- past EXIT
1892
1893       if Token = Tok_Identifier then
1894          Set_Name (Exit_Node, P_Qualified_Simple_Name);
1895
1896       elsif Style_Check then
1897          --  This EXIT has no name, so check that
1898          --  the innermost loop is unnamed too.
1899
1900          Check_No_Exit_Name :
1901          for J in reverse 1 .. Scope.Last loop
1902             if Scope.Table (J).Etyp = E_Loop then
1903                if Present (Scope.Table (J).Labl)
1904                  and then Comes_From_Source (Scope.Table (J).Labl)
1905                then
1906                   --  Innermost loop in fact had a name, style check fails
1907
1908                   Style.No_Exit_Name (Scope.Table (J).Labl);
1909                end if;
1910
1911                exit Check_No_Exit_Name;
1912             end if;
1913          end loop Check_No_Exit_Name;
1914       end if;
1915
1916       if Token = Tok_When and then not Missing_Semicolon_On_Exit then
1917          Scan; -- past WHEN
1918          Set_Condition (Exit_Node, P_Condition);
1919
1920       --  Allow IF instead of WHEN, giving error message
1921
1922       elsif Token = Tok_If then
1923          T_When;
1924          Scan; -- past IF used in place of WHEN
1925          Set_Condition (Exit_Node, P_Expression_No_Right_Paren);
1926       end if;
1927
1928       TF_Semicolon;
1929       return Exit_Node;
1930    end P_Exit_Statement;
1931
1932    -------------------------
1933    -- 5.8  Goto Statement --
1934    -------------------------
1935
1936    --  GOTO_STATEMENT ::= goto label_NAME;
1937
1938    --  The caller has checked that the initial token is GOTO  (or TO in the
1939    --  error case where GO and TO were incorrectly separated).
1940
1941    --  Error recovery: can raise Error_Resync
1942
1943    function P_Goto_Statement return Node_Id is
1944       Goto_Node : Node_Id;
1945
1946    begin
1947       Goto_Node := New_Node (N_Goto_Statement, Token_Ptr);
1948       Scan; -- past GOTO (or TO)
1949       Set_Name (Goto_Node, P_Qualified_Simple_Name_Resync);
1950       Append_Elmt (Goto_Node, Goto_List);
1951       No_Constraint;
1952       TF_Semicolon;
1953       return Goto_Node;
1954    end P_Goto_Statement;
1955
1956    ---------------------------
1957    -- Parse_Decls_Begin_End --
1958    ---------------------------
1959
1960    --  This function parses the construct:
1961
1962    --      DECLARATIVE_PART
1963    --    begin
1964    --      HANDLED_SEQUENCE_OF_STATEMENTS
1965    --    end [NAME];
1966
1967    --  The caller has built the scope stack entry, and created the node to
1968    --  whose Declarations and Handled_Statement_Sequence fields are to be
1969    --  set. On return these fields are filled in (except in the case of a
1970    --  task body, where the handled statement sequence is optional, and may
1971    --  thus be Empty), and the scan is positioned past the End sequence.
1972
1973    --  If the BEGIN is missing, then the parent node is used to help construct
1974    --  an appropriate missing BEGIN message. Possibilities for the parent are:
1975
1976    --    N_Block_Statement     declare block
1977    --    N_Entry_Body          entry body
1978    --    N_Package_Body        package body (begin part optional)
1979    --    N_Subprogram_Body     procedure or function body
1980    --    N_Task_Body           task body
1981
1982    --  Note: in the case of a block statement, there is definitely a DECLARE
1983    --  present (because a Begin statement without a DECLARE is handled by the
1984    --  P_Begin_Statement procedure, which does not call Parse_Decls_Begin_End.
1985
1986    --  Error recovery: cannot raise Error_Resync
1987
1988    procedure Parse_Decls_Begin_End (Parent : Node_Id) is
1989       Body_Decl    : Node_Id;
1990       Body_Sloc    : Source_Ptr;
1991       Decls        : List_Id;
1992       Decl         : Node_Id;
1993       Parent_Nkind : Node_Kind;
1994       Spec_Node    : Node_Id;
1995       HSS          : Node_Id;
1996
1997       procedure Missing_Begin (Msg : String);
1998       --  Called to post a missing begin message. In the normal case this is
1999       --  posted at the start of the current token. A special case arises when
2000       --  P_Declarative_Items has previously found a missing begin, in which
2001       --  case we replace the original error message.
2002
2003       procedure Set_Null_HSS (Parent : Node_Id);
2004       --  Construct an empty handled statement sequence and install in Parent
2005       --  Leaves HSS set to reference the newly constructed statement sequence.
2006
2007       -------------------
2008       -- Missing_Begin --
2009       -------------------
2010
2011       procedure Missing_Begin (Msg : String) is
2012       begin
2013          if Missing_Begin_Msg = No_Error_Msg then
2014             Error_Msg_BC (Msg);
2015          else
2016             Change_Error_Text (Missing_Begin_Msg, Msg);
2017
2018             --  Purge any messages issued after than, since a missing begin
2019             --  can cause a lot of havoc, and it is better not to dump these
2020             --  cascaded messages on the user.
2021
2022             Purge_Messages (Get_Location (Missing_Begin_Msg), Prev_Token_Ptr);
2023          end if;
2024       end Missing_Begin;
2025
2026       ------------------
2027       -- Set_Null_HSS --
2028       ------------------
2029
2030       procedure Set_Null_HSS (Parent : Node_Id) is
2031          Null_Stm : Node_Id;
2032
2033       begin
2034          Null_Stm :=
2035            Make_Null_Statement (Token_Ptr);
2036          Set_Comes_From_Source (Null_Stm, False);
2037
2038          HSS :=
2039            Make_Handled_Sequence_Of_Statements (Token_Ptr,
2040              Statements => New_List (Null_Stm));
2041          Set_Comes_From_Source (HSS, False);
2042
2043          Set_Handled_Statement_Sequence (Parent, HSS);
2044       end Set_Null_HSS;
2045
2046    --  Start of processing for Parse_Decls_Begin_End
2047
2048    begin
2049       Decls := P_Declarative_Part;
2050
2051       --  Check for misplacement of later vs basic declarations in Ada 83
2052
2053       if Ada_Version = Ada_83 then
2054          Decl := First (Decls);
2055
2056          --  Loop through sequence of basic declarative items
2057
2058          Outer : while Present (Decl) loop
2059             if Nkind (Decl) /= N_Subprogram_Body
2060               and then Nkind (Decl) /= N_Package_Body
2061               and then Nkind (Decl) /= N_Task_Body
2062               and then Nkind (Decl) not in  N_Body_Stub
2063             then
2064                Next (Decl);
2065
2066             --  Once a body is encountered, we only allow later declarative
2067             --  items. The inner loop checks the rest of the list.
2068
2069             else
2070                Body_Sloc := Sloc (Decl);
2071
2072                Inner : while Present (Decl) loop
2073                   if Nkind (Decl) not in N_Later_Decl_Item
2074                     and then Nkind (Decl) /= N_Pragma
2075                   then
2076                      if Ada_Version = Ada_83 then
2077                         Error_Msg_Sloc := Body_Sloc;
2078                         Error_Msg_N
2079                           ("(Ada 83) decl cannot appear after body#", Decl);
2080                      end if;
2081                   end if;
2082
2083                   Next (Decl);
2084                end loop Inner;
2085             end if;
2086          end loop Outer;
2087       end if;
2088
2089       --  Here is where we deal with the case of IS used instead of semicolon.
2090       --  Specifically, if the last declaration in the declarative part is a
2091       --  subprogram body still marked as having a bad IS, then this is where
2092       --  we decide that the IS should really have been a semicolon and that
2093       --  the body should have been a declaration. Note that if the bad IS
2094       --  had turned out to be OK (i.e. a decent begin/end was found for it),
2095       --  then the Bad_Is_Detected flag would have been reset by now.
2096
2097       Body_Decl := Last (Decls);
2098
2099       if Present (Body_Decl)
2100         and then Nkind (Body_Decl) = N_Subprogram_Body
2101         and then Bad_Is_Detected (Body_Decl)
2102       then
2103          --  OK, we have the case of a bad IS, so we need to fix up the tree.
2104          --  What we have now is a subprogram body with attached declarations
2105          --  and a possible statement sequence.
2106
2107          --  First step is to take the declarations that were part of the bogus
2108          --  subprogram body and append them to the outer declaration chain.
2109          --  In other words we append them past the body (which we will later
2110          --  convert into a declaration).
2111
2112          Append_List (Declarations (Body_Decl), Decls);
2113
2114          --  Now take the handled statement sequence of the bogus body and
2115          --  set it as the statement sequence for the outer construct. Note
2116          --  that it may be empty (we specially allowed a missing BEGIN for
2117          --  a subprogram body marked as having a bad IS -- see below).
2118
2119          Set_Handled_Statement_Sequence (Parent,
2120            Handled_Statement_Sequence (Body_Decl));
2121
2122          --  Next step is to convert the old body node to a declaration node
2123
2124          Spec_Node := Specification (Body_Decl);
2125          Change_Node (Body_Decl, N_Subprogram_Declaration);
2126          Set_Specification (Body_Decl, Spec_Node);
2127
2128          --  Final step is to put the declarations for the parent where
2129          --  they belong, and then fall through the IF to scan out the
2130          --  END statements.
2131
2132          Set_Declarations (Parent, Decls);
2133
2134       --  This is the normal case (i.e. any case except the bad IS case)
2135       --  If we have a BEGIN, then scan out the sequence of statements, and
2136       --  also reset the expected column for the END to match the BEGIN.
2137
2138       else
2139          Set_Declarations (Parent, Decls);
2140
2141          if Token = Tok_Begin then
2142             if Style_Check then
2143                Style.Check_Indentation;
2144             end if;
2145
2146             Error_Msg_Col := Scope.Table (Scope.Last).Ecol;
2147
2148             if RM_Column_Check
2149               and then Token_Is_At_Start_Of_Line
2150               and then Start_Column /= Error_Msg_Col
2151             then
2152                Error_Msg_SC ("(style) BEGIN in wrong column, should be@");
2153
2154             else
2155                Scope.Table (Scope.Last).Ecol := Start_Column;
2156             end if;
2157
2158             Scope.Table (Scope.Last).Sloc := Token_Ptr;
2159             Scan; -- past BEGIN
2160             Set_Handled_Statement_Sequence (Parent,
2161               P_Handled_Sequence_Of_Statements);
2162
2163          --  No BEGIN present
2164
2165          else
2166             Parent_Nkind := Nkind (Parent);
2167
2168             --  A special check for the missing IS case. If we have a
2169             --  subprogram body that was marked as having a suspicious
2170             --  IS, and the current token is END, then we simply confirm
2171             --  the suspicion, and do not require a BEGIN to be present
2172
2173             if Parent_Nkind = N_Subprogram_Body
2174               and then Token  = Tok_End
2175               and then Scope.Table (Scope.Last).Etyp = E_Suspicious_Is
2176             then
2177                Scope.Table (Scope.Last).Etyp := E_Bad_Is;
2178
2179             --  Otherwise BEGIN is not required for a package body, so we
2180             --  don't mind if it is missing, but we do construct a dummy
2181             --  one (so that we have somewhere to set End_Label).
2182
2183             --  However if we have something other than a BEGIN which
2184             --  looks like it might be statements, then we signal a missing
2185             --  BEGIN for these cases as well. We define "something which
2186             --  looks like it might be statements" as a token other than
2187             --  END, EOF, or a token which starts declarations.
2188
2189             elsif Parent_Nkind = N_Package_Body
2190               and then (Token = Tok_End
2191                           or else Token = Tok_EOF
2192                           or else Token in Token_Class_Declk)
2193             then
2194                Set_Null_HSS (Parent);
2195
2196             --  These are cases in which a BEGIN is required and not present
2197
2198             else
2199                Set_Null_HSS (Parent);
2200
2201                --  Prepare to issue error message
2202
2203                Error_Msg_Sloc := Scope.Table (Scope.Last).Sloc;
2204                Error_Msg_Node_1 := Scope.Table (Scope.Last).Labl;
2205
2206                --  Now issue appropriate message
2207
2208                if Parent_Nkind = N_Block_Statement then
2209                   Missing_Begin ("missing BEGIN for DECLARE#!");
2210
2211                elsif Parent_Nkind = N_Entry_Body then
2212                   Missing_Begin ("missing BEGIN for ENTRY#!");
2213
2214                elsif Parent_Nkind = N_Subprogram_Body then
2215                   if Nkind (Specification (Parent))
2216                                = N_Function_Specification
2217                   then
2218                      Missing_Begin ("missing BEGIN for function&#!");
2219                   else
2220                      Missing_Begin ("missing BEGIN for procedure&#!");
2221                   end if;
2222
2223                --  The case for package body arises only when
2224                --  we have possible statement junk present.
2225
2226                elsif Parent_Nkind = N_Package_Body then
2227                   Missing_Begin ("missing BEGIN for package body&#!");
2228
2229                else
2230                   pragma Assert (Parent_Nkind = N_Task_Body);
2231                   Missing_Begin ("missing BEGIN for task body&#!");
2232                end if;
2233
2234                --  Here we pick up the statements after the BEGIN that
2235                --  should have been present but was not. We don't insist
2236                --  on statements being present if P_Declarative_Part had
2237                --  already found a missing BEGIN, since it might have
2238                --  swallowed a lone statement into the declarative part.
2239
2240                if Missing_Begin_Msg /= No_Error_Msg
2241                  and then Token = Tok_End
2242                then
2243                   null;
2244                else
2245                   Set_Handled_Statement_Sequence (Parent,
2246                     P_Handled_Sequence_Of_Statements);
2247                end if;
2248             end if;
2249          end if;
2250       end if;
2251
2252       --  Here with declarations and handled statement sequence scanned
2253
2254       if Present (Handled_Statement_Sequence (Parent)) then
2255          End_Statements (Handled_Statement_Sequence (Parent));
2256       else
2257          End_Statements;
2258       end if;
2259
2260       --  We know that End_Statements removed an entry from the scope stack
2261       --  (because it is required to do so under all circumstances). We can
2262       --  therefore reference the entry it removed one past the stack top.
2263       --  What we are interested in is whether it was a case of a bad IS.
2264
2265       if Scope.Table (Scope.Last + 1).Etyp = E_Bad_Is then
2266          Error_Msg -- CODEFIX
2267            ("|IS should be "";""", Scope.Table (Scope.Last + 1).S_Is);
2268          Set_Bad_Is_Detected (Parent, True);
2269       end if;
2270
2271    end Parse_Decls_Begin_End;
2272
2273    -------------------------
2274    -- Set_Loop_Block_Name --
2275    -------------------------
2276
2277    function Set_Loop_Block_Name (L : Character) return Name_Id is
2278    begin
2279       Name_Buffer (1) := L;
2280       Name_Buffer (2) := '_';
2281       Name_Len := 2;
2282       Loop_Block_Count := Loop_Block_Count + 1;
2283       Add_Nat_To_Name_Buffer (Loop_Block_Count);
2284       return Name_Find;
2285    end Set_Loop_Block_Name;
2286
2287    ---------------
2288    -- Then_Scan --
2289    ---------------
2290
2291    procedure Then_Scan is
2292    begin
2293       TF_Then;
2294
2295       while Token = Tok_Then loop
2296          Error_Msg_SC -- CODEFIX
2297            ("redundant THEN");
2298          TF_Then;
2299       end loop;
2300
2301       if Token = Tok_And or else Token = Tok_Or then
2302          Error_Msg_SC ("unexpected logical operator");
2303          Scan; -- past logical operator
2304
2305          if (Prev_Token = Tok_And and then Token = Tok_Then)
2306               or else
2307             (Prev_Token = Tok_Or  and then Token = Tok_Else)
2308          then
2309             Scan;
2310          end if;
2311
2312          Discard_Junk_Node (P_Expression);
2313       end if;
2314
2315       if Token = Tok_Then then
2316          Scan;
2317       end if;
2318    end Then_Scan;
2319
2320 end Ch5;