[multiple changes]
[platform/upstream/gcc.git] / gcc / ada / par-ch6.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                              P A R . C H 6                               --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2009, 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 with Sinfo.CN; use Sinfo.CN;
31
32 separate (Par)
33 package body Ch6 is
34
35    --  Local subprograms, used only in this chapter
36
37    function P_Defining_Designator        return Node_Id;
38    function P_Defining_Operator_Symbol   return Node_Id;
39    function P_Return_Object_Declaration  return Node_Id;
40
41    procedure P_Return_Subtype_Indication (Decl_Node : Node_Id);
42    --  Decl_Node is a N_Object_Declaration.
43    --  Set the Null_Exclusion_Present and Object_Definition fields of
44    --  Decl_Node.
45
46    procedure Check_Junk_Semicolon_Before_Return;
47
48    --  Check for common error of junk semicolon before RETURN keyword of
49    --  function specification. If present, skip over it with appropriate
50    --  error message, leaving Scan_Ptr pointing to the RETURN after. This
51    --  routine also deals with a possibly misspelled version of Return.
52
53    ----------------------------------------
54    -- Check_Junk_Semicolon_Before_Return --
55    ----------------------------------------
56
57    procedure Check_Junk_Semicolon_Before_Return is
58       Scan_State : Saved_Scan_State;
59
60    begin
61       if Token = Tok_Semicolon then
62          Save_Scan_State (Scan_State);
63          Scan; -- past the semicolon
64
65          if Token = Tok_Return then
66             Restore_Scan_State (Scan_State);
67             Error_Msg_SC ("|extra "";"" ignored");
68             Scan; -- rescan past junk semicolon
69          else
70             Restore_Scan_State (Scan_State);
71          end if;
72
73       elsif Bad_Spelling_Of (Tok_Return) then
74          null;
75       end if;
76    end Check_Junk_Semicolon_Before_Return;
77
78    -----------------------------------------------------
79    -- 6.1  Subprogram (Also 6.3, 8.5.4, 10.1.3, 12.3) --
80    -----------------------------------------------------
81
82    --  This routine scans out a subprogram declaration, subprogram body,
83    --  subprogram renaming declaration or subprogram generic instantiation.
84
85    --  SUBPROGRAM_DECLARATION ::= SUBPROGRAM_SPECIFICATION;
86
87    --  ABSTRACT_SUBPROGRAM_DECLARATION ::=
88    --    SUBPROGRAM_SPECIFICATION is abstract;
89
90    --  SUBPROGRAM_SPECIFICATION ::=
91    --      procedure DEFINING_PROGRAM_UNIT_NAME PARAMETER_PROFILE
92    --    | function DEFINING_DESIGNATOR PARAMETER_AND_RESULT_PROFILE
93
94    --  PARAMETER_PROFILE ::= [FORMAL_PART]
95
96    --  PARAMETER_AND_RESULT_PROFILE ::= [FORMAL_PART] return SUBTYPE_MARK
97
98    --  SUBPROGRAM_BODY ::=
99    --    SUBPROGRAM_SPECIFICATION is
100    --      DECLARATIVE_PART
101    --    begin
102    --      HANDLED_SEQUENCE_OF_STATEMENTS
103    --    end [DESIGNATOR];
104
105    --  SUBPROGRAM_RENAMING_DECLARATION ::=
106    --    SUBPROGRAM_SPECIFICATION renames callable_entity_NAME;
107
108    --  SUBPROGRAM_BODY_STUB ::=
109    --    SUBPROGRAM_SPECIFICATION is separate;
110
111    --  GENERIC_INSTANTIATION ::=
112    --    procedure DEFINING_PROGRAM_UNIT_NAME is
113    --      new generic_procedure_NAME [GENERIC_ACTUAL_PART];
114    --  | function DEFINING_DESIGNATOR is
115    --      new generic_function_NAME [GENERIC_ACTUAL_PART];
116
117    --  NULL_PROCEDURE_DECLARATION ::=
118    --    SUBPROGRAM_SPECIFICATION is null;
119
120    --  Null procedures are an Ada 2005 feature. A null procedure declaration
121    --  is classified as a basic declarative item, but it is parsed here, with
122    --  other subprogram constructs.
123
124    --  The value in Pf_Flags indicates which of these possible declarations
125    --  is acceptable to the caller:
126
127    --    Pf_Flags.Decl                 Set if declaration OK
128    --    Pf_Flags.Gins                 Set if generic instantiation OK
129    --    Pf_Flags.Pbod                 Set if proper body OK
130    --    Pf_Flags.Rnam                 Set if renaming declaration OK
131    --    Pf_Flags.Stub                 Set if body stub OK
132
133    --  If an inappropriate form is encountered, it is scanned out but an
134    --  error message indicating that it is appearing in an inappropriate
135    --  context is issued. The only possible values for Pf_Flags are those
136    --  defined as constants in the Par package.
137
138    --  The caller has checked that the initial token is FUNCTION, PROCEDURE,
139    --  NOT or OVERRIDING.
140
141    --  Error recovery: cannot raise Error_Resync
142
143    function P_Subprogram (Pf_Flags : Pf_Rec) return Node_Id is
144       Specification_Node : Node_Id;
145       Name_Node          : Node_Id;
146       Fpart_List         : List_Id;
147       Fpart_Sloc         : Source_Ptr;
148       Result_Not_Null    : Boolean := False;
149       Result_Node        : Node_Id;
150       Inst_Node          : Node_Id;
151       Body_Node          : Node_Id;
152       Decl_Node          : Node_Id;
153       Rename_Node        : Node_Id;
154       Absdec_Node        : Node_Id;
155       Stub_Node          : Node_Id;
156       Fproc_Sloc         : Source_Ptr;
157       Func               : Boolean;
158       Scan_State         : Saved_Scan_State;
159
160       --  Flags for optional overriding indication. Two flags are needed,
161       --  to distinguish positive and negative overriding indicators from
162       --  the absence of any indicator.
163
164       Is_Overriding  : Boolean := False;
165       Not_Overriding : Boolean := False;
166
167    begin
168       --  Set up scope stack entry. Note that the Labl field will be set later
169
170       SIS_Entry_Active := False;
171       SIS_Missing_Semicolon_Message := No_Error_Msg;
172       Push_Scope_Stack;
173       Scope.Table (Scope.Last).Sloc := Token_Ptr;
174       Scope.Table (Scope.Last).Etyp := E_Name;
175       Scope.Table (Scope.Last).Ecol := Start_Column;
176       Scope.Table (Scope.Last).Lreq := False;
177
178       --  Ada2005: scan leading NOT OVERRIDING indicator
179
180       if Token = Tok_Not then
181          Scan;  -- past NOT
182
183          if Token = Tok_Overriding then
184             Scan;  --  past OVERRIDING
185             Not_Overriding := True;
186
187          --  Overriding keyword used in non Ada 2005 mode
188
189          elsif Token = Tok_Identifier
190            and then Token_Name = Name_Overriding
191          then
192             Error_Msg_SC ("overriding indicator is an Ada 2005 extension");
193             Error_Msg_SC ("\unit must be compiled with -gnat05 switch");
194             Scan;  --  past Overriding
195             Not_Overriding := True;
196
197          else
198             Error_Msg_SC ("OVERRIDING expected!");
199          end if;
200
201       --  Ada 2005: scan leading OVERRIDING indicator
202
203       --  Note: in the case of OVERRIDING keyword used in Ada 95 mode, the
204       --  declaration circuit already gave an error message and changed the
205       --  token to Tok_Overriding.
206
207       elsif Token = Tok_Overriding then
208          Scan;  --  past OVERRIDING
209          Is_Overriding := True;
210       end if;
211
212       if (Is_Overriding or else Not_Overriding) then
213
214          --  Note that if we are not in Ada_05 mode, error messages have
215          --  already been given, so no need to give another message here.
216
217          --  An overriding indicator is allowed for subprogram declarations,
218          --  bodies (including subunits), renamings, stubs, and
219          --  instantiations. The test against Pf_Decl_Pbod is added to account
220          --  for the case of subprograms declared in a protected type, where
221          --  only subprogram declarations and bodies can occur. The Pf_Pbod
222          --  case is for subunits.
223
224          if Pf_Flags /= Pf_Decl_Gins_Pbod_Rnam_Stub
225               and then
226             Pf_Flags /= Pf_Decl_Pbod
227               and then
228             Pf_Flags /= Pf_Pbod
229          then
230             Error_Msg_SC ("overriding indicator not allowed here!");
231
232          elsif Token /= Tok_Function and then Token /= Tok_Procedure then
233             Error_Msg_SC -- CODEFIX
234               ("FUNCTION or PROCEDURE expected!");
235          end if;
236       end if;
237
238       Func := (Token = Tok_Function);
239       Fproc_Sloc := Token_Ptr;
240       Scan; -- past FUNCTION or PROCEDURE
241       Ignore (Tok_Type);
242       Ignore (Tok_Body);
243
244       if Func then
245          Name_Node := P_Defining_Designator;
246
247          if Nkind (Name_Node) = N_Defining_Operator_Symbol
248            and then Scope.Last = 1
249          then
250             Error_Msg_SP ("operator symbol not allowed at library level");
251             Name_Node := New_Entity (N_Defining_Identifier, Sloc (Name_Node));
252
253             --  Set name from file name, we need some junk name, and that's
254             --  as good as anything. This is only approximate, since we do
255             --  not do anything with non-standard name translations.
256
257             Get_Name_String (File_Name (Current_Source_File));
258
259             for J in 1 .. Name_Len loop
260                if Name_Buffer (J) = '.' then
261                   Name_Len := J - 1;
262                   exit;
263                end if;
264             end loop;
265
266             Set_Chars (Name_Node, Name_Find);
267             Set_Error_Posted (Name_Node);
268          end if;
269
270       else
271          Name_Node := P_Defining_Program_Unit_Name;
272       end if;
273
274       Scope.Table (Scope.Last).Labl := Name_Node;
275       Ignore (Tok_Colon);
276
277       --  Deal with generic instantiation, the one case in which we do not
278       --  have a subprogram specification as part of whatever we are parsing
279
280       if Token = Tok_Is then
281          Save_Scan_State (Scan_State); -- at the IS
282          T_Is; -- checks for redundant IS
283
284          if Token = Tok_New then
285             if not Pf_Flags.Gins then
286                Error_Msg_SC ("generic instantiation not allowed here!");
287             end if;
288
289             Scan; -- past NEW
290
291             if Func then
292                Inst_Node := New_Node (N_Function_Instantiation, Fproc_Sloc);
293                Set_Name (Inst_Node, P_Function_Name);
294             else
295                Inst_Node := New_Node (N_Procedure_Instantiation, Fproc_Sloc);
296                Set_Name (Inst_Node, P_Qualified_Simple_Name);
297             end if;
298
299             Set_Defining_Unit_Name (Inst_Node, Name_Node);
300             Set_Generic_Associations (Inst_Node, P_Generic_Actual_Part_Opt);
301             TF_Semicolon;
302             Pop_Scope_Stack; -- Don't need scope stack entry in this case
303
304             if Is_Overriding then
305                Set_Must_Override (Inst_Node);
306
307             elsif Not_Overriding then
308                Set_Must_Not_Override (Inst_Node);
309             end if;
310
311             return Inst_Node;
312
313          else
314             Restore_Scan_State (Scan_State); -- to the IS
315          end if;
316       end if;
317
318       --  If not a generic instantiation, then we definitely have a subprogram
319       --  specification (all possibilities at this stage include one here)
320
321       Fpart_Sloc := Token_Ptr;
322
323       Check_Misspelling_Of (Tok_Return);
324
325       --  Scan formal part. First a special error check. If we have an
326       --  identifier here, then we have a definite error. If this identifier
327       --  is on the same line as the designator, then we assume it is the
328       --  first formal after a missing left parenthesis
329
330       if Token = Tok_Identifier
331         and then not Token_Is_At_Start_Of_Line
332       then
333             T_Left_Paren; -- to generate message
334             Fpart_List := P_Formal_Part;
335
336       --  Otherwise scan out an optional formal part in the usual manner
337
338       else
339          Fpart_List := P_Parameter_Profile;
340       end if;
341
342       --  We treat what we have as a function specification if FUNCTION was
343       --  used, or if a RETURN is present. This gives better error recovery
344       --  since later RETURN statements will be valid in either case.
345
346       Check_Junk_Semicolon_Before_Return;
347       Result_Node := Error;
348
349       if Token = Tok_Return then
350          if not Func then
351             Error_Msg ("PROCEDURE should be FUNCTION", Fproc_Sloc);
352             Func := True;
353          end if;
354
355          Scan; -- past RETURN
356
357          Result_Not_Null := P_Null_Exclusion;     --  Ada 2005 (AI-231)
358
359          --  Ada 2005 (AI-318-02)
360
361          if Token = Tok_Access then
362             if Ada_Version < Ada_05 then
363                Error_Msg_SC
364                  ("anonymous access result type is an Ada 2005 extension");
365                Error_Msg_SC ("\unit must be compiled with -gnat05 switch");
366             end if;
367
368             Result_Node := P_Access_Definition (Result_Not_Null);
369
370          else
371             Result_Node := P_Subtype_Mark;
372             No_Constraint;
373          end if;
374
375       else
376          if Func then
377             Ignore (Tok_Right_Paren);
378             TF_Return;
379          end if;
380       end if;
381
382       if Func then
383          Specification_Node :=
384            New_Node (N_Function_Specification, Fproc_Sloc);
385
386          Set_Null_Exclusion_Present (Specification_Node, Result_Not_Null);
387          Set_Result_Definition (Specification_Node, Result_Node);
388
389       else
390          Specification_Node :=
391            New_Node (N_Procedure_Specification, Fproc_Sloc);
392       end if;
393
394       Set_Defining_Unit_Name (Specification_Node, Name_Node);
395       Set_Parameter_Specifications (Specification_Node, Fpart_List);
396
397       if Is_Overriding then
398          Set_Must_Override (Specification_Node);
399
400       elsif Not_Overriding then
401          Set_Must_Not_Override (Specification_Node);
402       end if;
403
404       --  Error check: barriers not allowed on protected functions/procedures
405
406       if Token = Tok_When then
407          if Func then
408             Error_Msg_SC ("barrier not allowed on function, only on entry");
409          else
410             Error_Msg_SC ("barrier not allowed on procedure, only on entry");
411          end if;
412
413          Scan; -- past WHEN
414          Discard_Junk_Node (P_Expression);
415       end if;
416
417       --  Deal with semicolon followed by IS. We want to treat this as IS
418
419       if Token = Tok_Semicolon then
420          Save_Scan_State (Scan_State);
421          Scan; -- past semicolon
422
423          if Token = Tok_Is then
424             Error_Msg_SP ("extra "";"" ignored");
425          else
426             Restore_Scan_State (Scan_State);
427          end if;
428       end if;
429
430       --  Deal with case of semicolon ending a subprogram declaration
431
432       if Token = Tok_Semicolon then
433          if not Pf_Flags.Decl then
434             T_Is;
435          end if;
436
437          Scan; -- past semicolon
438
439          --  If semicolon is immediately followed by IS, then ignore the
440          --  semicolon, and go process the body.
441
442          if Token = Tok_Is then
443             Error_Msg_SP ("|extra "";"" ignored");
444             T_Is; -- scan past IS
445             goto Subprogram_Body;
446
447          --  If BEGIN follows in an appropriate column, we immediately
448          --  commence the error action of assuming that the previous
449          --  subprogram declaration should have been a subprogram body,
450          --  i.e. that the terminating semicolon should have been IS.
451
452          elsif Token = Tok_Begin
453             and then Start_Column >= Scope.Table (Scope.Last).Ecol
454          then
455             Error_Msg_SP ("|"";"" should be IS!");
456             goto Subprogram_Body;
457
458          else
459             goto Subprogram_Declaration;
460          end if;
461
462       --  Case of not followed by semicolon
463
464       else
465          --  Subprogram renaming declaration case
466
467          Check_Misspelling_Of (Tok_Renames);
468
469          if Token = Tok_Renames then
470             if not Pf_Flags.Rnam then
471                Error_Msg_SC ("renaming declaration not allowed here!");
472             end if;
473
474             Rename_Node :=
475               New_Node (N_Subprogram_Renaming_Declaration, Token_Ptr);
476             Scan; -- past RENAMES
477             Set_Name (Rename_Node, P_Name);
478             Set_Specification (Rename_Node, Specification_Node);
479             TF_Semicolon;
480             Pop_Scope_Stack;
481             return Rename_Node;
482
483          --  Case of IS following subprogram specification
484
485          elsif Token = Tok_Is then
486             T_Is; -- ignore redundant Is's
487
488             if Token_Name = Name_Abstract then
489                Check_95_Keyword (Tok_Abstract, Tok_Semicolon);
490             end if;
491
492             --  Deal nicely with (now obsolete) use of <> in place of abstract
493
494             if Token = Tok_Box then
495                Error_Msg_SC ("ABSTRACT expected");
496                Token := Tok_Abstract;
497             end if;
498
499             --  Abstract subprogram declaration case
500
501             if Token = Tok_Abstract then
502                Absdec_Node :=
503                  New_Node (N_Abstract_Subprogram_Declaration, Token_Ptr);
504                Set_Specification (Absdec_Node, Specification_Node);
505                Pop_Scope_Stack; -- discard unneeded entry
506                Scan; -- past ABSTRACT
507                TF_Semicolon;
508                return Absdec_Node;
509
510             --  Ada 2005 (AI-248): Parse a null procedure declaration
511
512             elsif Token = Tok_Null then
513                if Ada_Version < Ada_05 then
514                   Error_Msg_SP ("null procedures are an Ada 2005 extension");
515                   Error_Msg_SP ("\unit must be compiled with -gnat05 switch");
516                end if;
517
518                Scan; -- past NULL
519
520                if Func then
521                   Error_Msg_SP ("only procedures can be null");
522                else
523                   Set_Null_Present (Specification_Node);
524                end if;
525
526                TF_Semicolon;
527                goto Subprogram_Declaration;
528
529             --  Check for IS NEW with Formal_Part present and handle nicely
530
531             elsif Token = Tok_New then
532                Error_Msg
533                  ("formal part not allowed in instantiation", Fpart_Sloc);
534                Scan; -- past NEW
535
536                if Func then
537                   Inst_Node := New_Node (N_Function_Instantiation, Fproc_Sloc);
538                else
539                   Inst_Node :=
540                     New_Node (N_Procedure_Instantiation, Fproc_Sloc);
541                end if;
542
543                Set_Defining_Unit_Name (Inst_Node, Name_Node);
544                Set_Name (Inst_Node, P_Name);
545                Set_Generic_Associations (Inst_Node, P_Generic_Actual_Part_Opt);
546                TF_Semicolon;
547                Pop_Scope_Stack; -- Don't need scope stack entry in this case
548                return Inst_Node;
549
550             else
551                goto Subprogram_Body;
552             end if;
553
554          --  Here we have a missing IS or missing semicolon, we always guess
555          --  a missing semicolon, since we are pretty good at fixing up a
556          --  semicolon which should really be an IS
557
558          else
559             Error_Msg_AP ("|missing "";""");
560             SIS_Missing_Semicolon_Message := Get_Msg_Id;
561             goto Subprogram_Declaration;
562          end if;
563       end if;
564
565       --  Processing for subprogram body
566
567       <<Subprogram_Body>>
568          if not Pf_Flags.Pbod then
569             Error_Msg_SP ("subprogram body not allowed here!");
570          end if;
571
572          --  Subprogram body stub case
573
574          if Separate_Present then
575             if not Pf_Flags.Stub then
576                Error_Msg_SC ("body stub not allowed here!");
577             end if;
578
579             if Nkind (Name_Node) = N_Defining_Operator_Symbol then
580                Error_Msg
581                  ("operator symbol cannot be used as subunit name",
582                   Sloc (Name_Node));
583             end if;
584
585             Stub_Node :=
586               New_Node (N_Subprogram_Body_Stub, Sloc (Specification_Node));
587             Set_Specification (Stub_Node, Specification_Node);
588             Scan; -- past SEPARATE
589             Pop_Scope_Stack;
590             TF_Semicolon;
591             return Stub_Node;
592
593          --  Subprogram body case
594
595          else
596             --  Here is the test for a suspicious IS (i.e. one that looks
597             --  like it might more properly be a semicolon). See separate
598             --  section discussing use of IS instead of semicolon in
599             --  package Parse.
600
601             if (Token in Token_Class_Declk
602                   or else
603                 Token = Tok_Identifier)
604               and then Start_Column <= Scope.Table (Scope.Last).Ecol
605               and then Scope.Last /= 1
606             then
607                Scope.Table (Scope.Last).Etyp := E_Suspicious_Is;
608                Scope.Table (Scope.Last).S_Is := Prev_Token_Ptr;
609             end if;
610
611             Body_Node :=
612               New_Node (N_Subprogram_Body, Sloc (Specification_Node));
613             Set_Specification (Body_Node, Specification_Node);
614             Parse_Decls_Begin_End (Body_Node);
615             return Body_Node;
616          end if;
617
618       --  Processing for subprogram declaration
619
620       <<Subprogram_Declaration>>
621          Decl_Node :=
622            New_Node (N_Subprogram_Declaration, Sloc (Specification_Node));
623          Set_Specification (Decl_Node, Specification_Node);
624
625          --  If this is a context in which a subprogram body is permitted,
626          --  set active SIS entry in case (see section titled "Handling
627          --  Semicolon Used in Place of IS" in body of Parser package)
628          --  Note that SIS_Missing_Semicolon_Message is already set properly.
629
630          if Pf_Flags.Pbod then
631             SIS_Labl := Scope.Table (Scope.Last).Labl;
632             SIS_Sloc := Scope.Table (Scope.Last).Sloc;
633             SIS_Ecol := Scope.Table (Scope.Last).Ecol;
634             SIS_Declaration_Node := Decl_Node;
635             SIS_Semicolon_Sloc := Prev_Token_Ptr;
636             SIS_Entry_Active := True;
637          end if;
638
639          Pop_Scope_Stack;
640          return Decl_Node;
641
642    end P_Subprogram;
643
644    ---------------------------------
645    -- 6.1  Subprogram Declaration --
646    ---------------------------------
647
648    --  Parsed by P_Subprogram (6.1)
649
650    ------------------------------------------
651    -- 6.1  Abstract Subprogram Declaration --
652    ------------------------------------------
653
654    --  Parsed by P_Subprogram (6.1)
655
656    -----------------------------------
657    -- 6.1  Subprogram Specification --
658    -----------------------------------
659
660    --  SUBPROGRAM_SPECIFICATION ::=
661    --      procedure DEFINING_PROGRAM_UNIT_NAME PARAMETER_PROFILE
662    --    | function DEFINING_DESIGNATOR PARAMETER_AND_RESULT_PROFILE
663
664    --  PARAMETER_PROFILE ::= [FORMAL_PART]
665
666    --  PARAMETER_AND_RESULT_PROFILE ::= [FORMAL_PART] return SUBTYPE_MARK
667
668    --  Subprogram specifications that appear in subprogram declarations
669    --  are parsed by P_Subprogram (6.1). This routine is used in other
670    --  contexts where subprogram specifications occur.
671
672    --  Note: this routine does not affect the scope stack in any way
673
674    --  Error recovery: can raise Error_Resync
675
676    function P_Subprogram_Specification return Node_Id is
677       Specification_Node : Node_Id;
678       Result_Not_Null    : Boolean;
679       Result_Node        : Node_Id;
680
681    begin
682       if Token = Tok_Function then
683          Specification_Node := New_Node (N_Function_Specification, Token_Ptr);
684          Scan; -- past FUNCTION
685          Ignore (Tok_Body);
686          Set_Defining_Unit_Name (Specification_Node, P_Defining_Designator);
687          Set_Parameter_Specifications
688            (Specification_Node, P_Parameter_Profile);
689          Check_Junk_Semicolon_Before_Return;
690          TF_Return;
691
692          Result_Not_Null := P_Null_Exclusion;     --  Ada 2005 (AI-231)
693
694          --  Ada 2005 (AI-318-02)
695
696          if Token = Tok_Access then
697             if Ada_Version < Ada_05 then
698                Error_Msg_SC
699                  ("anonymous access result type is an Ada 2005 extension");
700                Error_Msg_SC ("\unit must be compiled with -gnat05 switch");
701             end if;
702
703             Result_Node := P_Access_Definition (Result_Not_Null);
704
705          else
706             Result_Node := P_Subtype_Mark;
707             No_Constraint;
708          end if;
709
710          Set_Null_Exclusion_Present (Specification_Node, Result_Not_Null);
711          Set_Result_Definition (Specification_Node, Result_Node);
712          return Specification_Node;
713
714       elsif Token = Tok_Procedure then
715          Specification_Node := New_Node (N_Procedure_Specification, Token_Ptr);
716          Scan; -- past PROCEDURE
717          Ignore (Tok_Body);
718          Set_Defining_Unit_Name
719            (Specification_Node, P_Defining_Program_Unit_Name);
720          Set_Parameter_Specifications
721            (Specification_Node, P_Parameter_Profile);
722          return Specification_Node;
723
724       else
725          Error_Msg_SC ("subprogram specification expected");
726          raise Error_Resync;
727       end if;
728    end P_Subprogram_Specification;
729
730    ---------------------
731    -- 6.1  Designator --
732    ---------------------
733
734    --  DESIGNATOR ::=
735    --    [PARENT_UNIT_NAME .] IDENTIFIER | OPERATOR_SYMBOL
736
737    --  The caller has checked that the initial token is an identifier,
738    --  operator symbol, or string literal. Note that we don't bother to
739    --  do much error diagnosis in this routine, since it is only used for
740    --  the label on END lines, and the routines in package Par.Endh will
741    --  check that the label is appropriate.
742
743    --  Error recovery: cannot raise Error_Resync
744
745    function P_Designator return Node_Id is
746       Ident_Node  : Node_Id;
747       Name_Node   : Node_Id;
748       Prefix_Node : Node_Id;
749
750       function Real_Dot return Boolean;
751       --  Tests if a current token is an interesting period, i.e. is followed
752       --  by an identifier or operator symbol or string literal. If not, it is
753       --  probably just incorrect punctuation to be caught by our caller. Note
754       --  that the case of an operator symbol or string literal is also an
755       --  error, but that is an error that we catch here. If the result is
756       --  True, a real dot has been scanned and we are positioned past it,
757       --  if the result is False, the scan position is unchanged.
758
759       --------------
760       -- Real_Dot --
761       --------------
762
763       function Real_Dot return Boolean is
764          Scan_State  : Saved_Scan_State;
765
766       begin
767          if Token /= Tok_Dot then
768             return False;
769
770          else
771             Save_Scan_State (Scan_State);
772             Scan; -- past dot
773
774             if Token = Tok_Identifier
775               or else Token = Tok_Operator_Symbol
776               or else Token = Tok_String_Literal
777             then
778                return True;
779
780             else
781                Restore_Scan_State (Scan_State);
782                return False;
783             end if;
784          end if;
785       end Real_Dot;
786
787    --  Start of processing for P_Designator
788
789    begin
790       Ident_Node := Token_Node;
791       Scan; -- past initial token
792
793       if Prev_Token = Tok_Operator_Symbol
794         or else Prev_Token = Tok_String_Literal
795         or else not Real_Dot
796       then
797          return Ident_Node;
798
799       --  Child name case
800
801       else
802          Prefix_Node := Ident_Node;
803
804          --  Loop through child names, on entry to this loop, Prefix contains
805          --  the name scanned so far, and Ident_Node is the last identifier.
806
807          loop
808             Name_Node := New_Node (N_Selected_Component, Prev_Token_Ptr);
809             Set_Prefix (Name_Node, Prefix_Node);
810             Ident_Node := P_Identifier;
811             Set_Selector_Name (Name_Node, Ident_Node);
812             Prefix_Node := Name_Node;
813             exit when not Real_Dot;
814          end loop;
815
816          --  On exit from the loop, Ident_Node is the last identifier scanned,
817          --  i.e. the defining identifier, and Prefix_Node is a node for the
818          --  entire name, structured (incorrectly!) as a selected component.
819
820          Name_Node := Prefix (Prefix_Node);
821          Change_Node (Prefix_Node, N_Designator);
822          Set_Name (Prefix_Node, Name_Node);
823          Set_Identifier (Prefix_Node, Ident_Node);
824          return Prefix_Node;
825       end if;
826
827    exception
828       when Error_Resync =>
829          while Token = Tok_Dot or else Token = Tok_Identifier loop
830             Scan;
831          end loop;
832
833          return Error;
834    end P_Designator;
835
836    ------------------------------
837    -- 6.1  Defining Designator --
838    ------------------------------
839
840    --  DEFINING_DESIGNATOR ::=
841    --    DEFINING_PROGRAM_UNIT_NAME | DEFINING_OPERATOR_SYMBOL
842
843    --  Error recovery: cannot raise Error_Resync
844
845    function P_Defining_Designator return Node_Id is
846    begin
847       if Token = Tok_Operator_Symbol then
848          return P_Defining_Operator_Symbol;
849
850       elsif Token = Tok_String_Literal then
851          Error_Msg_SC ("invalid operator name");
852          Scan; -- past junk string
853          return Error;
854
855       else
856          return P_Defining_Program_Unit_Name;
857       end if;
858    end P_Defining_Designator;
859
860    -------------------------------------
861    -- 6.1  Defining Program Unit Name --
862    -------------------------------------
863
864    --  DEFINING_PROGRAM_UNIT_NAME ::=
865    --    [PARENT_UNIT_NAME .] DEFINING_IDENTIFIER
866
867    --  Note: PARENT_UNIT_NAME may be present only in 95 mode at the outer level
868
869    --  Error recovery: cannot raise Error_Resync
870
871    function P_Defining_Program_Unit_Name return Node_Id is
872       Ident_Node  : Node_Id;
873       Name_Node   : Node_Id;
874       Prefix_Node : Node_Id;
875
876    begin
877       --  Set identifier casing if not already set and scan initial identifier
878
879       if Token = Tok_Identifier
880         and then Identifier_Casing (Current_Source_File) = Unknown
881       then
882          Set_Identifier_Casing (Current_Source_File, Determine_Token_Casing);
883       end if;
884
885       Ident_Node := P_Identifier (C_Dot);
886       Merge_Identifier (Ident_Node, Tok_Return);
887
888       --  Normal case (not child library unit name)
889
890       if Token /= Tok_Dot then
891          Change_Identifier_To_Defining_Identifier (Ident_Node);
892          return Ident_Node;
893
894       --  Child library unit name case
895
896       else
897          if Scope.Last > 1 then
898             Error_Msg_SP ("child unit allowed only at library level");
899             raise Error_Resync;
900
901          elsif Ada_Version = Ada_83 then
902             Error_Msg_SP ("(Ada 83) child unit not allowed!");
903
904          end if;
905
906          Prefix_Node := Ident_Node;
907
908          --  Loop through child names, on entry to this loop, Prefix contains
909          --  the name scanned so far, and Ident_Node is the last identifier.
910
911          loop
912             exit when Token /= Tok_Dot;
913             Name_Node := New_Node (N_Selected_Component, Token_Ptr);
914             Scan; -- past period
915             Set_Prefix (Name_Node, Prefix_Node);
916             Ident_Node := P_Identifier (C_Dot);
917             Set_Selector_Name (Name_Node, Ident_Node);
918             Prefix_Node := Name_Node;
919          end loop;
920
921          --  On exit from the loop, Ident_Node is the last identifier scanned,
922          --  i.e. the defining identifier, and Prefix_Node is a node for the
923          --  entire name, structured (incorrectly!) as a selected component.
924
925          Name_Node := Prefix (Prefix_Node);
926          Change_Node (Prefix_Node, N_Defining_Program_Unit_Name);
927          Set_Name (Prefix_Node, Name_Node);
928          Change_Identifier_To_Defining_Identifier (Ident_Node);
929          Set_Defining_Identifier (Prefix_Node, Ident_Node);
930
931          --  All set with unit name parsed
932
933          return Prefix_Node;
934       end if;
935
936    exception
937       when Error_Resync =>
938          while Token = Tok_Dot or else Token = Tok_Identifier loop
939             Scan;
940          end loop;
941
942          return Error;
943    end P_Defining_Program_Unit_Name;
944
945    --------------------------
946    -- 6.1  Operator Symbol --
947    --------------------------
948
949    --  OPERATOR_SYMBOL ::= STRING_LITERAL
950
951    --  Operator symbol is returned by the scanner as Tok_Operator_Symbol
952
953    -----------------------------------
954    -- 6.1  Defining Operator Symbol --
955    -----------------------------------
956
957    --  DEFINING_OPERATOR_SYMBOL ::= OPERATOR_SYMBOL
958
959    --  The caller has checked that the initial symbol is an operator symbol
960
961    function P_Defining_Operator_Symbol return Node_Id is
962       Op_Node : Node_Id;
963
964    begin
965       Op_Node := Token_Node;
966       Change_Operator_Symbol_To_Defining_Operator_Symbol (Op_Node);
967       Scan; -- past operator symbol
968       return Op_Node;
969    end P_Defining_Operator_Symbol;
970
971    ----------------------------
972    -- 6.1  Parameter_Profile --
973    ----------------------------
974
975    --  PARAMETER_PROFILE ::= [FORMAL_PART]
976
977    --  Empty is returned if no formal part is present
978
979    --  Error recovery: cannot raise Error_Resync
980
981    function P_Parameter_Profile return List_Id is
982    begin
983       if Token = Tok_Left_Paren then
984          Scan; -- part left paren
985          return P_Formal_Part;
986       else
987          return No_List;
988       end if;
989    end P_Parameter_Profile;
990
991    ---------------------------------------
992    -- 6.1  Parameter And Result Profile --
993    ---------------------------------------
994
995    --  Parsed by its parent construct, which uses P_Parameter_Profile to
996    --  parse the parameters, and P_Subtype_Mark to parse the return type.
997
998    ----------------------
999    -- 6.1  Formal part --
1000    ----------------------
1001
1002    --  FORMAL_PART ::= (PARAMETER_SPECIFICATION {; PARAMETER_SPECIFICATION})
1003
1004    --  PARAMETER_SPECIFICATION ::=
1005    --    DEFINING_IDENTIFIER_LIST : MODE [NULL_EXCLUSION] SUBTYPE_MARK
1006    --      [:= DEFAULT_EXPRESSION]
1007    --  | DEFINING_IDENTIFIER_LIST : ACCESS_DEFINITION
1008    --      [:= DEFAULT_EXPRESSION]
1009
1010    --  This scans the construct Formal_Part. The caller has already checked
1011    --  that the initial token is a left parenthesis, and skipped past it, so
1012    --  that on entry Token is the first token following the left parenthesis.
1013
1014    --  Error recovery: cannot raise Error_Resync
1015
1016    function P_Formal_Part return List_Id is
1017       Specification_List : List_Id;
1018       Specification_Node : Node_Id;
1019       Scan_State         : Saved_Scan_State;
1020       Num_Idents         : Nat;
1021       Ident              : Nat;
1022       Ident_Sloc         : Source_Ptr;
1023       Not_Null_Present   : Boolean := False;
1024       Not_Null_Sloc      : Source_Ptr;
1025
1026       Idents : array (Int range 1 .. 4096) of Entity_Id;
1027       --  This array holds the list of defining identifiers. The upper bound
1028       --  of 4096 is intended to be essentially infinite, and we do not even
1029       --  bother to check for it being exceeded.
1030
1031    begin
1032       Specification_List := New_List;
1033       Specification_Loop : loop
1034          begin
1035             if Token = Tok_Pragma then
1036                Error_Msg_SC ("pragma not allowed in formal part");
1037                Discard_Junk_Node (P_Pragma (Skipping => True));
1038             end if;
1039
1040             Ignore (Tok_Left_Paren);
1041             Ident_Sloc := Token_Ptr;
1042             Idents (1) := P_Defining_Identifier (C_Comma_Colon);
1043             Num_Idents := 1;
1044
1045             Ident_Loop : loop
1046                exit Ident_Loop when Token = Tok_Colon;
1047
1048                --  The only valid tokens are colon and comma, so if we have
1049                --  neither do a bit of investigation to see which is the
1050                --  better choice for insertion.
1051
1052                if Token /= Tok_Comma then
1053
1054                   --  Assume colon if IN or OUT keyword found
1055
1056                   exit Ident_Loop when Token = Tok_In or else Token = Tok_Out;
1057
1058                   --  Otherwise scan ahead
1059
1060                   Save_Scan_State (Scan_State);
1061                   Look_Ahead : loop
1062
1063                      --  If we run into a semicolon, then assume that a
1064                      --  colon was missing, e.g.  Parms (X Y; ...). Also
1065                      --  assume missing colon on EOF (a real disaster!)
1066                      --  and on a right paren, e.g. Parms (X Y), and also
1067                      --  on an assignment symbol, e.g. Parms (X Y := ..)
1068
1069                      if Token = Tok_Semicolon
1070                        or else Token = Tok_Right_Paren
1071                        or else Token = Tok_EOF
1072                        or else Token = Tok_Colon_Equal
1073                      then
1074                         Restore_Scan_State (Scan_State);
1075                         exit Ident_Loop;
1076
1077                      --  If we run into a colon, assume that we had a missing
1078                      --  comma, e.g. Parms (A B : ...). Also assume a missing
1079                      --  comma if we hit another comma, e.g. Parms (A B, C ..)
1080
1081                      elsif Token = Tok_Colon
1082                        or else Token = Tok_Comma
1083                      then
1084                         Restore_Scan_State (Scan_State);
1085                         exit Look_Ahead;
1086                      end if;
1087
1088                      Scan;
1089                   end loop Look_Ahead;
1090                end if;
1091
1092                --  Here if a comma is present, or to be assumed
1093
1094                T_Comma;
1095                Num_Idents := Num_Idents + 1;
1096                Idents (Num_Idents) := P_Defining_Identifier (C_Comma_Colon);
1097             end loop Ident_Loop;
1098
1099             --  Fall through the loop on encountering a colon, or deciding
1100             --  that there is a missing colon.
1101
1102             T_Colon;
1103
1104             --  If there are multiple identifiers, we repeatedly scan the
1105             --  type and initialization expression information by resetting
1106             --  the scan pointer (so that we get completely separate trees
1107             --  for each occurrence).
1108
1109             if Num_Idents > 1 then
1110                Save_Scan_State (Scan_State);
1111             end if;
1112
1113             --  Loop through defining identifiers in list
1114
1115             Ident := 1;
1116
1117             Ident_List_Loop : loop
1118                Specification_Node :=
1119                  New_Node (N_Parameter_Specification, Ident_Sloc);
1120                Set_Defining_Identifier (Specification_Node, Idents (Ident));
1121
1122                --  Scan possible NOT NULL for Ada 2005 (AI-231, AI-447)
1123
1124                Not_Null_Sloc := Token_Ptr;
1125                Not_Null_Present :=
1126                  P_Null_Exclusion (Allow_Anonymous_In_95 => True);
1127
1128                --  Case of ACCESS keyword present
1129
1130                if Token = Tok_Access then
1131                   Set_Null_Exclusion_Present
1132                     (Specification_Node, Not_Null_Present);
1133
1134                   if Ada_Version = Ada_83 then
1135                      Error_Msg_SC ("(Ada 83) access parameters not allowed");
1136                   end if;
1137
1138                   Set_Parameter_Type
1139                     (Specification_Node,
1140                      P_Access_Definition (Not_Null_Present));
1141
1142                --  Case of IN or OUT present
1143
1144                else
1145                   if Token = Tok_In or else Token = Tok_Out then
1146                      if Not_Null_Present then
1147                         Error_Msg
1148                           ("`NOT NULL` can only be used with `ACCESS`",
1149                            Not_Null_Sloc);
1150
1151                         if Token = Tok_In then
1152                            Error_Msg
1153                              ("\`IN` not allowed together with `ACCESS`",
1154                               Not_Null_Sloc);
1155                         else
1156                            Error_Msg
1157                              ("\`OUT` not allowed together with `ACCESS`",
1158                               Not_Null_Sloc);
1159                         end if;
1160                      end if;
1161
1162                      P_Mode (Specification_Node);
1163                      Not_Null_Present := P_Null_Exclusion; -- Ada 2005 (AI-231)
1164                   end if;
1165
1166                   Set_Null_Exclusion_Present
1167                     (Specification_Node, Not_Null_Present);
1168
1169                   if Token = Tok_Procedure
1170                        or else
1171                      Token = Tok_Function
1172                   then
1173                      Error_Msg_SC ("formal subprogram parameter not allowed");
1174                      Scan;
1175
1176                      if Token = Tok_Left_Paren then
1177                         Discard_Junk_List (P_Formal_Part);
1178                      end if;
1179
1180                      if Token = Tok_Return then
1181                         Scan;
1182                         Discard_Junk_Node (P_Subtype_Mark);
1183                      end if;
1184
1185                      Set_Parameter_Type (Specification_Node, Error);
1186
1187                   else
1188                      Set_Parameter_Type (Specification_Node, P_Subtype_Mark);
1189                      No_Constraint;
1190                   end if;
1191                end if;
1192
1193                Set_Expression (Specification_Node, Init_Expr_Opt (True));
1194
1195                if Ident > 1 then
1196                   Set_Prev_Ids (Specification_Node, True);
1197                end if;
1198
1199                if Ident < Num_Idents then
1200                   Set_More_Ids (Specification_Node, True);
1201                end if;
1202
1203                Append (Specification_Node, Specification_List);
1204                exit Ident_List_Loop when Ident = Num_Idents;
1205                Ident := Ident + 1;
1206                Restore_Scan_State (Scan_State);
1207             end loop Ident_List_Loop;
1208
1209          exception
1210             when Error_Resync =>
1211                Resync_Semicolon_List;
1212          end;
1213
1214          if Token = Tok_Semicolon then
1215             Save_Scan_State (Scan_State);
1216             Scan; -- past semicolon
1217
1218             --  If we have RETURN or IS after the semicolon, then assume
1219             --  that semicolon should have been a right parenthesis and exit
1220
1221             if Token = Tok_Is or else Token = Tok_Return then
1222                Error_Msg_SP ("|"";"" should be "")""");
1223                exit Specification_Loop;
1224             end if;
1225
1226             --  If we have a declaration keyword after the semicolon, then
1227             --  assume we had a missing right parenthesis and terminate list
1228
1229             if Token in Token_Class_Declk then
1230                Error_Msg_AP ("missing "")""");
1231                Restore_Scan_State (Scan_State);
1232                exit Specification_Loop;
1233             end if;
1234
1235          elsif Token = Tok_Right_Paren then
1236             Scan; -- past right paren
1237             exit Specification_Loop;
1238
1239          --  Special check for common error of using comma instead of semicolon
1240
1241          elsif Token = Tok_Comma then
1242             T_Semicolon;
1243             Scan; -- past comma
1244
1245          --  Special check for omitted separator
1246
1247          elsif Token = Tok_Identifier then
1248             T_Semicolon;
1249
1250          --  If nothing sensible, skip to next semicolon or right paren
1251
1252          else
1253             T_Semicolon;
1254             Resync_Semicolon_List;
1255
1256             if Token = Tok_Semicolon then
1257                Scan; -- past semicolon
1258             else
1259                T_Right_Paren;
1260                exit Specification_Loop;
1261             end if;
1262          end if;
1263       end loop Specification_Loop;
1264
1265       return Specification_List;
1266    end P_Formal_Part;
1267
1268    ----------------------------------
1269    -- 6.1  Parameter Specification --
1270    ----------------------------------
1271
1272    --  Parsed by P_Formal_Part (6.1)
1273
1274    ---------------
1275    -- 6.1  Mode --
1276    ---------------
1277
1278    --  MODE ::= [in] | in out | out
1279
1280    --  There is no explicit node in the tree for the Mode. Instead the
1281    --  In_Present and Out_Present flags are set in the parent node to
1282    --  record the presence of keywords specifying the mode.
1283
1284    --  Error_Recovery: cannot raise Error_Resync
1285
1286    procedure P_Mode (Node : Node_Id) is
1287    begin
1288       if Token = Tok_In then
1289          Scan; -- past IN
1290          Set_In_Present (Node, True);
1291
1292          if Style.Mode_In_Check and then Token /= Tok_Out then
1293             Error_Msg_SP ("(style) IN should be omitted");
1294          end if;
1295
1296          if Token = Tok_Access then
1297             Error_Msg_SP ("IN not allowed together with ACCESS");
1298             Scan; -- past ACCESS
1299          end if;
1300       end if;
1301
1302       if Token = Tok_Out then
1303          Scan; -- past OUT
1304          Set_Out_Present (Node, True);
1305       end if;
1306
1307       if Token = Tok_In then
1308          Error_Msg_SC -- CODEFIX ???
1309            ("IN must precede OUT in parameter mode");
1310          Scan; -- past IN
1311          Set_In_Present (Node, True);
1312       end if;
1313    end P_Mode;
1314
1315    --------------------------
1316    -- 6.3  Subprogram Body --
1317    --------------------------
1318
1319    --  Parsed by P_Subprogram (6.1)
1320
1321    -----------------------------------
1322    -- 6.4  Procedure Call Statement --
1323    -----------------------------------
1324
1325    --  Parsed by P_Sequence_Of_Statements (5.1)
1326
1327    ------------------------
1328    -- 6.4  Function Call --
1329    ------------------------
1330
1331    --  Parsed by P_Call_Or_Name (4.1)
1332
1333    --------------------------------
1334    -- 6.4  Actual Parameter Part --
1335    --------------------------------
1336
1337    --  Parsed by P_Call_Or_Name (4.1)
1338
1339    --------------------------------
1340    -- 6.4  Parameter Association --
1341    --------------------------------
1342
1343    --  Parsed by P_Call_Or_Name (4.1)
1344
1345    ------------------------------------
1346    -- 6.4  Explicit Actual Parameter --
1347    ------------------------------------
1348
1349    --  Parsed by P_Call_Or_Name (4.1)
1350
1351    ---------------------------
1352    -- 6.5  Return Statement --
1353    ---------------------------
1354
1355    --  SIMPLE_RETURN_STATEMENT ::= return [EXPRESSION];
1356    --
1357    --  EXTENDED_RETURN_STATEMENT ::=
1358    --    return DEFINING_IDENTIFIER : [aliased] RETURN_SUBTYPE_INDICATION
1359    --                                           [:= EXPRESSION] [do
1360    --      HANDLED_SEQUENCE_OF_STATEMENTS
1361    --    end return];
1362    --
1363    --  RETURN_SUBTYPE_INDICATION ::= SUBTYPE_INDICATION | ACCESS_DEFINITION
1364
1365    --  RETURN_STATEMENT ::= return [EXPRESSION];
1366
1367    --  Error recovery: can raise Error_Resync
1368
1369    procedure P_Return_Subtype_Indication (Decl_Node : Node_Id) is
1370
1371       --  Note: We don't need to check Ada_Version here, because this is
1372       --  only called in >= Ada 2005 cases anyway.
1373
1374       Not_Null_Present : constant Boolean := P_Null_Exclusion;
1375
1376    begin
1377       Set_Null_Exclusion_Present (Decl_Node, Not_Null_Present);
1378
1379       if Token = Tok_Access then
1380          Set_Object_Definition
1381            (Decl_Node, P_Access_Definition (Not_Null_Present));
1382       else
1383          Set_Object_Definition
1384            (Decl_Node, P_Subtype_Indication (Not_Null_Present));
1385       end if;
1386    end P_Return_Subtype_Indication;
1387
1388    --  Error recovery: can raise Error_Resync
1389
1390    function P_Return_Object_Declaration return Node_Id is
1391       Return_Obj : Node_Id;
1392       Decl_Node  : Node_Id;
1393
1394    begin
1395       Return_Obj := Token_Node;
1396       Change_Identifier_To_Defining_Identifier (Return_Obj);
1397       Decl_Node := New_Node (N_Object_Declaration, Token_Ptr);
1398       Set_Defining_Identifier (Decl_Node, Return_Obj);
1399
1400       Scan; -- past identifier
1401       Scan; -- past :
1402
1403       --  First an error check, if we have two identifiers in a row, a likely
1404       --  possibility is that the first of the identifiers is an incorrectly
1405       --  spelled keyword. See similar check in P_Identifier_Declarations.
1406
1407       if Token = Tok_Identifier then
1408          declare
1409             SS : Saved_Scan_State;
1410             I2 : Boolean;
1411
1412          begin
1413             Save_Scan_State (SS);
1414             Scan; -- past initial identifier
1415             I2 := (Token = Tok_Identifier);
1416             Restore_Scan_State (SS);
1417
1418             if I2
1419               and then
1420                 (Bad_Spelling_Of (Tok_Access)   or else
1421                  Bad_Spelling_Of (Tok_Aliased)  or else
1422                  Bad_Spelling_Of (Tok_Constant))
1423             then
1424                null;
1425             end if;
1426          end;
1427       end if;
1428
1429       --  We allow "constant" here (as in "return Result : constant
1430       --  T..."). This is not in the latest RM, but the ARG is considering an
1431       --  AI on the subject (see AI05-0015-1), which we expect to be approved.
1432
1433       if Token = Tok_Constant then
1434          Scan; -- past CONSTANT
1435          Set_Constant_Present (Decl_Node);
1436
1437          if Token = Tok_Aliased then
1438             Error_Msg_SC -- CODEFIX
1439               ("ALIASED should be before CONSTANT");
1440             Scan; -- past ALIASED
1441             Set_Aliased_Present (Decl_Node);
1442          end if;
1443
1444       elsif Token = Tok_Aliased then
1445          Scan; -- past ALIASED
1446          Set_Aliased_Present (Decl_Node);
1447
1448          if Token = Tok_Constant then
1449             Scan; -- past CONSTANT
1450             Set_Constant_Present (Decl_Node);
1451          end if;
1452       end if;
1453
1454       P_Return_Subtype_Indication (Decl_Node);
1455
1456       if Token = Tok_Colon_Equal then
1457          Scan; -- past :=
1458          Set_Expression (Decl_Node, P_Expression_No_Right_Paren);
1459       end if;
1460
1461       return Decl_Node;
1462    end P_Return_Object_Declaration;
1463
1464    --  Error recovery: can raise Error_Resync
1465
1466    function P_Return_Statement return Node_Id is
1467       --  The caller has checked that the initial token is RETURN
1468
1469       function Is_Simple return Boolean;
1470       --  Scan state is just after RETURN (and is left that way).
1471       --  Determine whether this is a simple or extended return statement
1472       --  by looking ahead for "identifier :", which implies extended.
1473
1474       ---------------
1475       -- Is_Simple --
1476       ---------------
1477
1478       function Is_Simple return Boolean is
1479          Scan_State : Saved_Scan_State;
1480          Result     : Boolean := True;
1481
1482       begin
1483          if Token = Tok_Identifier then
1484             Save_Scan_State (Scan_State); -- at identifier
1485             Scan; -- past identifier
1486
1487             if Token = Tok_Colon then
1488                Result := False; -- It's an extended_return_statement.
1489             end if;
1490
1491             Restore_Scan_State (Scan_State); -- to identifier
1492          end if;
1493
1494          return Result;
1495       end Is_Simple;
1496
1497       Return_Sloc : constant Source_Ptr := Token_Ptr;
1498       Return_Node : Node_Id;
1499
1500    --  Start of processing for P_Return_Statement
1501
1502    begin
1503       Scan; -- past RETURN
1504
1505       --  Simple_return_statement, no expression, return an
1506       --  N_Simple_Return_Statement node with the expression field left Empty.
1507
1508       if Token = Tok_Semicolon then
1509          Scan; -- past ;
1510          Return_Node := New_Node (N_Simple_Return_Statement, Return_Sloc);
1511
1512       --  Non-trivial case
1513
1514       else
1515          --  Simple_return_statement with expression
1516
1517          --  We avoid trying to scan an expression if we are at an
1518          --  expression terminator since in that case the best error
1519          --  message is probably that we have a missing semicolon.
1520
1521          if Is_Simple then
1522             Return_Node := New_Node (N_Simple_Return_Statement, Return_Sloc);
1523
1524             if Token not in Token_Class_Eterm then
1525                Set_Expression (Return_Node, P_Expression_No_Right_Paren);
1526             end if;
1527
1528          --  Extended_return_statement (Ada 2005 only -- AI-318):
1529
1530          else
1531             if Ada_Version < Ada_05 then
1532                Error_Msg_SP
1533                  (" extended_return_statement is an Ada 2005 extension");
1534                Error_Msg_SP ("\unit must be compiled with -gnat05 switch");
1535             end if;
1536
1537             Return_Node := New_Node (N_Extended_Return_Statement, Return_Sloc);
1538             Set_Return_Object_Declarations
1539               (Return_Node, New_List (P_Return_Object_Declaration));
1540
1541             if Token = Tok_Do then
1542                Push_Scope_Stack;
1543                Scope.Table (Scope.Last).Etyp := E_Return;
1544                Scope.Table (Scope.Last).Ecol := Start_Column;
1545                Scope.Table (Scope.Last).Sloc := Return_Sloc;
1546
1547                Scan; -- past DO
1548                Set_Handled_Statement_Sequence
1549                  (Return_Node, P_Handled_Sequence_Of_Statements);
1550                End_Statements;
1551
1552                --  Do we need to handle Error_Resync here???
1553             end if;
1554          end if;
1555
1556          TF_Semicolon;
1557       end if;
1558
1559       return Return_Node;
1560    end P_Return_Statement;
1561
1562 end Ch6;