OSDN Git Service

2007-08-16 Robert Dewar <dewar@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / par-ch12.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             P A R . C H 1 2                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2007, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 2,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT;  see file COPYING.  If not, write --
19 -- to  the  Free Software Foundation,  51  Franklin  Street,  Fifth  Floor, --
20 -- Boston, MA 02110-1301, USA.                                              --
21 --                                                                          --
22 -- GNAT was originally developed  by the GNAT team at  New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
24 --                                                                          --
25 ------------------------------------------------------------------------------
26
27 pragma Style_Checks (All_Checks);
28 --  Turn off subprogram body ordering check. Subprograms are in order
29 --  by RM section rather than alphabetical
30
31 separate (Par)
32 package body Ch12 is
33
34    --  Local functions, used only in this chapter
35
36    function P_Formal_Derived_Type_Definition           return Node_Id;
37    function P_Formal_Discrete_Type_Definition          return Node_Id;
38    function P_Formal_Fixed_Point_Definition            return Node_Id;
39    function P_Formal_Floating_Point_Definition         return Node_Id;
40    function P_Formal_Modular_Type_Definition           return Node_Id;
41    function P_Formal_Package_Declaration               return Node_Id;
42    function P_Formal_Private_Type_Definition           return Node_Id;
43    function P_Formal_Signed_Integer_Type_Definition    return Node_Id;
44    function P_Formal_Subprogram_Declaration            return Node_Id;
45    function P_Formal_Type_Declaration                  return Node_Id;
46    function P_Formal_Type_Definition                   return Node_Id;
47    function P_Generic_Association                      return Node_Id;
48
49    procedure P_Formal_Object_Declarations (Decls : List_Id);
50    --  Scans one or more formal object declarations and appends them to
51    --  Decls. Scans more than one declaration only in the case where the
52    --  source has a declaration with multiple defining identifiers.
53
54    --------------------------------
55    -- 12.1  Generic (also 8.5.5) --
56    --------------------------------
57
58    --  This routine parses either one of the forms of a generic declaration
59    --  or a generic renaming declaration.
60
61    --  GENERIC_DECLARATION ::=
62    --    GENERIC_SUBPROGRAM_DECLARATION | GENERIC_PACKAGE_DECLARATION
63
64    --  GENERIC_SUBPROGRAM_DECLARATION ::=
65    --    GENERIC_FORMAL_PART SUBPROGRAM_SPECIFICATION;
66
67    --  GENERIC_PACKAGE_DECLARATION ::=
68    --    GENERIC_FORMAL_PART PACKAGE_SPECIFICATION;
69
70    --  GENERIC_FORMAL_PART ::=
71    --    generic {GENERIC_FORMAL_PARAMETER_DECLARATION | USE_CLAUSE}
72
73    --  GENERIC_RENAMING_DECLARATION ::=
74    --    generic package DEFINING_PROGRAM_UNIT_NAME
75    --      renames generic_package_NAME
76    --  | generic procedure DEFINING_PROGRAM_UNIT_NAME
77    --      renames generic_procedure_NAME
78    --  | generic function DEFINING_PROGRAM_UNIT_NAME
79    --      renames generic_function_NAME
80
81    --  GENERIC_FORMAL_PARAMETER_DECLARATION ::=
82    --    FORMAL_OBJECT_DECLARATION
83    --  | FORMAL_TYPE_DECLARATION
84    --  | FORMAL_SUBPROGRAM_DECLARATION
85    --  | FORMAL_PACKAGE_DECLARATION
86
87    --  The caller has checked that the initial token is GENERIC
88
89    --  Error recovery: can raise Error_Resync
90
91    function P_Generic return Node_Id is
92       Gen_Sloc   : constant Source_Ptr := Token_Ptr;
93       Gen_Decl   : Node_Id;
94       Decl_Node  : Node_Id;
95       Decls      : List_Id;
96       Def_Unit   : Node_Id;
97       Ren_Token  : Token_Type;
98       Scan_State : Saved_Scan_State;
99
100    begin
101       Scan; -- past GENERIC
102
103       if Token = Tok_Private then
104          Error_Msg_SC ("PRIVATE goes before GENERIC, not after");
105          Scan; -- past junk PRIVATE token
106       end if;
107
108       Save_Scan_State (Scan_State); -- at token past GENERIC
109
110       --  Check for generic renaming declaration case
111
112       if Token = Tok_Package
113         or else Token = Tok_Function
114         or else Token = Tok_Procedure
115       then
116          Ren_Token := Token;
117          Scan; -- scan past PACKAGE, FUNCTION or PROCEDURE
118
119          if Token = Tok_Identifier then
120             Def_Unit := P_Defining_Program_Unit_Name;
121
122             Check_Misspelling_Of (Tok_Renames);
123
124             if Token = Tok_Renames then
125                if Ren_Token = Tok_Package then
126                   Decl_Node := New_Node
127                     (N_Generic_Package_Renaming_Declaration, Gen_Sloc);
128
129                elsif Ren_Token = Tok_Procedure then
130                   Decl_Node := New_Node
131                     (N_Generic_Procedure_Renaming_Declaration, Gen_Sloc);
132
133                else -- Ren_Token = Tok_Function then
134                   Decl_Node := New_Node
135                     (N_Generic_Function_Renaming_Declaration, Gen_Sloc);
136                end if;
137
138                Scan; -- past RENAMES
139                Set_Defining_Unit_Name (Decl_Node, Def_Unit);
140                Set_Name (Decl_Node, P_Name);
141                TF_Semicolon;
142                return Decl_Node;
143             end if;
144          end if;
145       end if;
146
147       --  Fall through if this is *not* a generic renaming declaration
148
149       Restore_Scan_State (Scan_State);
150       Decls := New_List;
151
152       --  Loop through generic parameter declarations and use clauses
153
154       Decl_Loop : loop
155          P_Pragmas_Opt (Decls);
156
157          if Token = Tok_Private then
158             Error_Msg_S ("generic private child packages not permitted");
159             Scan; -- past PRIVATE
160          end if;
161
162          if Token = Tok_Use then
163             Append (P_Use_Clause, Decls);
164          else
165             --  Parse a generic parameter declaration
166
167             if Token = Tok_Identifier then
168                P_Formal_Object_Declarations (Decls);
169
170             elsif Token = Tok_Type then
171                Append (P_Formal_Type_Declaration, Decls);
172
173             elsif Token = Tok_With then
174                Scan; -- past WITH
175
176                if Token = Tok_Package then
177                   Append (P_Formal_Package_Declaration, Decls);
178
179                elsif Token = Tok_Procedure or Token = Tok_Function then
180                   Append (P_Formal_Subprogram_Declaration, Decls);
181
182                else
183                   Error_Msg_BC
184                     ("FUNCTION, PROCEDURE or PACKAGE expected here");
185                   Resync_Past_Semicolon;
186                end if;
187
188             elsif Token = Tok_Subtype then
189                Error_Msg_SC ("subtype declaration not allowed " &
190                                 "as generic parameter declaration!");
191                Resync_Past_Semicolon;
192
193             else
194                exit Decl_Loop;
195             end if;
196          end if;
197
198       end loop Decl_Loop;
199
200       --  Generic formal part is scanned, scan out subprogram or package spec
201
202       if Token = Tok_Package then
203          Gen_Decl := New_Node (N_Generic_Package_Declaration, Gen_Sloc);
204          Set_Specification (Gen_Decl, P_Package (Pf_Spcn));
205       else
206          Gen_Decl := New_Node (N_Generic_Subprogram_Declaration, Gen_Sloc);
207
208          Set_Specification (Gen_Decl, P_Subprogram_Specification);
209
210          if Nkind (Defining_Unit_Name (Specification (Gen_Decl))) =
211                                              N_Defining_Program_Unit_Name
212            and then Scope.Last > 0
213          then
214             Error_Msg_SP ("child unit allowed only at library level");
215          end if;
216          TF_Semicolon;
217       end if;
218
219       Set_Generic_Formal_Declarations (Gen_Decl, Decls);
220       return Gen_Decl;
221    end P_Generic;
222
223    -------------------------------
224    -- 12.1  Generic Declaration --
225    -------------------------------
226
227    --  Parsed by P_Generic (12.1)
228
229    ------------------------------------------
230    -- 12.1  Generic Subprogram Declaration --
231    ------------------------------------------
232
233    --  Parsed by P_Generic (12.1)
234
235    ---------------------------------------
236    -- 12.1  Generic Package Declaration --
237    ---------------------------------------
238
239    --  Parsed by P_Generic (12.1)
240
241    -------------------------------
242    -- 12.1  Generic Formal Part --
243    -------------------------------
244
245    --  Parsed by P_Generic (12.1)
246
247    -------------------------------------------------
248    -- 12.1   Generic Formal Parameter Declaration --
249    -------------------------------------------------
250
251    --  Parsed by P_Generic (12.1)
252
253    ---------------------------------
254    -- 12.3  Generic Instantiation --
255    ---------------------------------
256
257    --  Generic package instantiation parsed by P_Package (7.1)
258    --  Generic procedure instantiation parsed by P_Subprogram (6.1)
259    --  Generic function instantiation parsed by P_Subprogram (6.1)
260
261    -------------------------------
262    -- 12.3  Generic Actual Part --
263    -------------------------------
264
265    --  GENERIC_ACTUAL_PART ::=
266    --    (GENERIC_ASSOCIATION {, GENERIC_ASSOCIATION})
267
268    --  Returns a list of generic associations, or Empty if none are present
269
270    --  Error recovery: cannot raise Error_Resync
271
272    function P_Generic_Actual_Part_Opt return List_Id is
273       Association_List : List_Id;
274
275    begin
276       --  Figure out if a generic actual part operation is present. Clearly
277       --  there is no generic actual part if the current token is semicolon
278
279       if Token = Tok_Semicolon then
280          return No_List;
281
282       --  If we don't have a left paren, then we have an error, and the job
283       --  is to figure out whether a left paren or semicolon was intended.
284       --  We assume a missing left paren (and hence a generic actual part
285       --  present) if the current token is not on a new line, or if it is
286       --  indented from the subprogram token. Otherwise assume missing
287       --  semicolon (which will be diagnosed by caller) and no generic part
288
289       elsif Token /= Tok_Left_Paren
290         and then Token_Is_At_Start_Of_Line
291         and then Start_Column <= Scope.Table (Scope.Last).Ecol
292       then
293          return No_List;
294
295       --  Otherwise we have a generic actual part (either a left paren is
296       --  present, or we have decided that there must be a missing left paren)
297
298       else
299          Association_List := New_List;
300          T_Left_Paren;
301
302          loop
303             Append (P_Generic_Association, Association_List);
304             exit when not Comma_Present;
305          end loop;
306
307          T_Right_Paren;
308          return Association_List;
309       end if;
310
311    end P_Generic_Actual_Part_Opt;
312
313    -------------------------------
314    -- 12.3  Generic Association --
315    -------------------------------
316
317    --  GENERIC_ASSOCIATION ::=
318    --    [generic_formal_parameter_SELECTOR_NAME =>]
319    --      EXPLICIT_GENERIC_ACTUAL_PARAMETER
320
321    --  EXPLICIT_GENERIC_ACTUAL_PARAMETER ::=
322    --    EXPRESSION      | variable_NAME   | subprogram_NAME
323    --  | entry_NAME      | SUBTYPE_MARK    | package_instance_NAME
324
325    --  Error recovery: cannot raise Error_Resync
326
327    function P_Generic_Association return Node_Id is
328       Scan_State         : Saved_Scan_State;
329       Param_Name_Node    : Node_Id;
330       Generic_Assoc_Node : Node_Id;
331
332    begin
333       Generic_Assoc_Node := New_Node (N_Generic_Association, Token_Ptr);
334
335       --  Ada2005: an association can be given by: others => <>
336
337       if Token = Tok_Others then
338          if Ada_Version < Ada_05 then
339             Error_Msg_SP
340               ("partial parametrization of formal packages" &
341                 " is an Ada 2005 extension");
342             Error_Msg_SP
343               ("\unit must be compiled with -gnat05 switch");
344          end if;
345
346          Scan;  --  past OTHERS
347
348          if Token /= Tok_Arrow then
349             Error_Msg_BC ("expect arrow after others");
350          else
351             Scan;  --  past arrow
352          end if;
353
354          if Token /= Tok_Box then
355             Error_Msg_BC ("expect Box after arrow");
356          else
357             Scan;  --  past box
358          end if;
359
360          --  Source position of the others choice is beginning of construct
361
362          return New_Node (N_Others_Choice, Sloc (Generic_Assoc_Node));
363       end if;
364
365       if Token in Token_Class_Desig then
366          Param_Name_Node := Token_Node;
367          Save_Scan_State (Scan_State); -- at designator
368          Scan; -- past simple name or operator symbol
369
370          if Token = Tok_Arrow then
371             Scan; -- past arrow
372             Set_Selector_Name (Generic_Assoc_Node, Param_Name_Node);
373          else
374             Restore_Scan_State (Scan_State); -- to designator
375          end if;
376       end if;
377
378       --  In Ada 2005 the actual can be a box
379
380       if Token = Tok_Box then
381          Scan;
382          Set_Box_Present (Generic_Assoc_Node);
383          Set_Explicit_Generic_Actual_Parameter (Generic_Assoc_Node, Empty);
384
385       else
386          Set_Explicit_Generic_Actual_Parameter
387            (Generic_Assoc_Node, P_Expression);
388       end if;
389
390       return Generic_Assoc_Node;
391    end P_Generic_Association;
392
393    ---------------------------------------------
394    -- 12.3  Explicit Generic Actual Parameter --
395    ---------------------------------------------
396
397    --  Parsed by P_Generic_Association (12.3)
398
399    --------------------------------------
400    -- 12.4  Formal Object Declarations --
401    --------------------------------------
402
403    --  FORMAL_OBJECT_DECLARATION ::=
404    --    DEFINING_IDENTIFIER_LIST :
405    --      MODE [NULL_EXCLUSION] SUBTYPE_MARK [:= DEFAULT_EXPRESSION];
406    --  | DEFINING_IDENTIFIER_LIST :
407    --      MODE ACCESS_DEFINITION [:= DEFAULT_EXPRESSION];
408
409    --  The caller has checked that the initial token is an identifier
410
411    --  Error recovery: cannot raise Error_Resync
412
413    procedure P_Formal_Object_Declarations (Decls : List_Id) is
414       Decl_Node        : Node_Id;
415       Ident            : Nat;
416       Not_Null_Present : Boolean := False;
417       Num_Idents       : Nat;
418       Scan_State       : Saved_Scan_State;
419
420       Idents : array (Int range 1 .. 4096) of Entity_Id;
421       --  This array holds the list of defining identifiers. The upper bound
422       --  of 4096 is intended to be essentially infinite, and we do not even
423       --  bother to check for it being exceeded.
424
425    begin
426       Idents (1) := P_Defining_Identifier (C_Comma_Colon);
427       Num_Idents := 1;
428
429       while Comma_Present loop
430          Num_Idents := Num_Idents + 1;
431          Idents (Num_Idents) := P_Defining_Identifier (C_Comma_Colon);
432       end loop;
433
434       T_Colon;
435
436       --  If there are multiple identifiers, we repeatedly scan the
437       --  type and initialization expression information by resetting
438       --  the scan pointer (so that we get completely separate trees
439       --  for each occurrence).
440
441       if Num_Idents > 1 then
442          Save_Scan_State (Scan_State);
443       end if;
444
445       --  Loop through defining identifiers in list
446
447       Ident := 1;
448       Ident_Loop : loop
449          Decl_Node := New_Node (N_Formal_Object_Declaration, Token_Ptr);
450          Set_Defining_Identifier (Decl_Node, Idents (Ident));
451          P_Mode (Decl_Node);
452
453          Not_Null_Present := P_Null_Exclusion;  --  Ada 2005 (AI-423)
454
455          --  Ada 2005 (AI-423): Formal object with an access definition
456
457          if Token = Tok_Access then
458
459             --  The access definition is still parsed and set even though
460             --  the compilation may not use the proper switch. This action
461             --  ensures the required local error recovery.
462
463             Set_Access_Definition (Decl_Node,
464               P_Access_Definition (Not_Null_Present));
465
466             if Ada_Version < Ada_05 then
467                Error_Msg_SP
468                  ("access definition not allowed in formal object " &
469                   "declaration");
470                Error_Msg_SP ("\unit must be compiled with -gnat05 switch");
471             end if;
472
473          --  Formal object with a subtype mark
474
475          else
476             Set_Null_Exclusion_Present (Decl_Node, Not_Null_Present);
477             Set_Subtype_Mark (Decl_Node, P_Subtype_Mark_Resync);
478          end if;
479
480          No_Constraint;
481          Set_Default_Expression (Decl_Node, Init_Expr_Opt);
482
483          if Ident > 1 then
484             Set_Prev_Ids (Decl_Node, True);
485          end if;
486
487          if Ident < Num_Idents then
488             Set_More_Ids (Decl_Node, True);
489          end if;
490
491          Append (Decl_Node, Decls);
492
493          exit Ident_Loop when Ident = Num_Idents;
494          Ident := Ident + 1;
495          Restore_Scan_State (Scan_State);
496       end loop Ident_Loop;
497
498       TF_Semicolon;
499    end P_Formal_Object_Declarations;
500
501    -----------------------------------
502    -- 12.5  Formal Type Declaration --
503    -----------------------------------
504
505    --  FORMAL_TYPE_DECLARATION ::=
506    --    type DEFINING_IDENTIFIER [DISCRIMINANT_PART]
507    --      is FORMAL_TYPE_DEFINITION;
508
509    --  The caller has checked that the initial token is TYPE
510
511    --  Error recovery: cannot raise Error_Resync
512
513    function P_Formal_Type_Declaration return Node_Id is
514       Decl_Node  : Node_Id;
515       Def_Node   : Node_Id;
516
517    begin
518       Decl_Node := New_Node (N_Formal_Type_Declaration, Token_Ptr);
519       Scan; -- past TYPE
520       Set_Defining_Identifier (Decl_Node, P_Defining_Identifier);
521
522       if P_Unknown_Discriminant_Part_Opt then
523          Set_Unknown_Discriminants_Present (Decl_Node, True);
524       else
525          Set_Discriminant_Specifications
526            (Decl_Node, P_Known_Discriminant_Part_Opt);
527       end if;
528
529       T_Is;
530
531       Def_Node := P_Formal_Type_Definition;
532
533       if Def_Node /= Error then
534          Set_Formal_Type_Definition (Decl_Node, Def_Node);
535          TF_Semicolon;
536
537       else
538          Decl_Node := Error;
539
540          --  If we have semicolon, skip it to avoid cascaded errors
541
542          if Token = Tok_Semicolon then
543             Scan;
544          end if;
545       end if;
546
547       return Decl_Node;
548    end P_Formal_Type_Declaration;
549
550    ----------------------------------
551    -- 12.5  Formal Type Definition --
552    ----------------------------------
553
554    --  FORMAL_TYPE_DEFINITION ::=
555    --    FORMAL_PRIVATE_TYPE_DEFINITION
556    --  | FORMAL_DERIVED_TYPE_DEFINITION
557    --  | FORMAL_DISCRETE_TYPE_DEFINITION
558    --  | FORMAL_SIGNED_INTEGER_TYPE_DEFINITION
559    --  | FORMAL_MODULAR_TYPE_DEFINITION
560    --  | FORMAL_FLOATING_POINT_DEFINITION
561    --  | FORMAL_ORDINARY_FIXED_POINT_DEFINITION
562    --  | FORMAL_DECIMAL_FIXED_POINT_DEFINITION
563    --  | FORMAL_ARRAY_TYPE_DEFINITION
564    --  | FORMAL_ACCESS_TYPE_DEFINITION
565    --  | FORMAL_INTERFACE_TYPE_DEFINITION
566
567    --  FORMAL_ARRAY_TYPE_DEFINITION ::= ARRAY_TYPE_DEFINITION
568
569    --  FORMAL_ACCESS_TYPE_DEFINITION ::= ACCESS_TYPE_DEFINITION
570
571    --  FORMAL_INTERFACE_TYPE_DEFINITION ::= INTERFACE_TYPE_DEFINITION
572
573    function P_Formal_Type_Definition return Node_Id is
574       Scan_State   : Saved_Scan_State;
575       Typedef_Node : Node_Id;
576
577    begin
578       if Token_Name = Name_Abstract then
579          Check_95_Keyword (Tok_Abstract, Tok_Tagged);
580       end if;
581
582       if Token_Name = Name_Tagged then
583          Check_95_Keyword (Tok_Tagged, Tok_Private);
584          Check_95_Keyword (Tok_Tagged, Tok_Limited);
585       end if;
586
587       case Token is
588
589          --  Mostly we can tell what we have from the initial token. The one
590          --  exception is ABSTRACT, where we have to scan ahead to see if we
591          --  have a formal derived type or a formal private type definition.
592
593          --  In addition, in Ada 2005 LIMITED may appear after abstract, so
594          --  that the lookahead must be extended by one more token.
595
596          when Tok_Abstract =>
597             Save_Scan_State (Scan_State);
598             Scan; -- past ABSTRACT
599
600             if Token = Tok_New then
601                Restore_Scan_State (Scan_State); -- to ABSTRACT
602                return P_Formal_Derived_Type_Definition;
603
604             elsif Token = Tok_Limited then
605                Scan;  --  past LIMITED
606
607                if Token = Tok_New then
608                   Restore_Scan_State (Scan_State); -- to ABSTRACT
609                   return P_Formal_Derived_Type_Definition;
610
611                else
612                   Restore_Scan_State (Scan_State); -- to ABSTRACT
613                   return P_Formal_Private_Type_Definition;
614                end if;
615
616             --  Ada 2005 (AI-443): Abstract synchronized formal derived type
617
618             elsif Token = Tok_Synchronized then
619                Restore_Scan_State (Scan_State); -- to ABSTRACT
620                return P_Formal_Derived_Type_Definition;
621
622             else
623                Restore_Scan_State (Scan_State); -- to ABSTRACT
624                return P_Formal_Private_Type_Definition;
625             end if;
626
627          when Tok_Access =>
628             return P_Access_Type_Definition;
629
630          when Tok_Array =>
631             return P_Array_Type_Definition;
632
633          when Tok_Delta =>
634             return P_Formal_Fixed_Point_Definition;
635
636          when Tok_Digits =>
637             return P_Formal_Floating_Point_Definition;
638
639          when Tok_Interface => --  Ada 2005 (AI-251)
640             return P_Interface_Type_Definition (Abstract_Present => False);
641
642          when Tok_Left_Paren =>
643             return P_Formal_Discrete_Type_Definition;
644
645          when Tok_Limited =>
646             Save_Scan_State (Scan_State);
647             Scan; --  past LIMITED
648
649             if Token = Tok_Interface then
650                Typedef_Node :=
651                  P_Interface_Type_Definition (Abstract_Present => False);
652                Set_Limited_Present (Typedef_Node);
653                return Typedef_Node;
654
655             elsif Token = Tok_New then
656                Restore_Scan_State (Scan_State); -- to LIMITED
657                return P_Formal_Derived_Type_Definition;
658
659             else
660                if Token = Tok_Abstract then
661                   Error_Msg_SC ("ABSTRACT must come before LIMITED");
662                   Scan;  --  past improper ABSTRACT
663
664                   if Token = Tok_New then
665                      Restore_Scan_State (Scan_State); -- to LIMITED
666                      return P_Formal_Derived_Type_Definition;
667
668                   else
669                      Restore_Scan_State (Scan_State);
670                      return P_Formal_Private_Type_Definition;
671                   end if;
672                end if;
673
674                Restore_Scan_State (Scan_State);
675                return P_Formal_Private_Type_Definition;
676             end if;
677
678          when Tok_Mod =>
679             return P_Formal_Modular_Type_Definition;
680
681          when Tok_New =>
682             return P_Formal_Derived_Type_Definition;
683
684          when Tok_Not =>
685             if P_Null_Exclusion then
686                Typedef_Node :=  P_Access_Type_Definition;
687                Set_Null_Exclusion_Present (Typedef_Node);
688                return Typedef_Node;
689
690             else
691                Error_Msg_SC ("expect valid formal access definition!");
692                Resync_Past_Semicolon;
693                return Error;
694             end if;
695
696          when Tok_Private |
697               Tok_Tagged  =>
698             return P_Formal_Private_Type_Definition;
699
700          when Tok_Range =>
701             return P_Formal_Signed_Integer_Type_Definition;
702
703          when Tok_Record =>
704             Error_Msg_SC ("record not allowed in generic type definition!");
705             Discard_Junk_Node (P_Record_Definition);
706             return Error;
707
708          --  Ada 2005 (AI-345): Task, Protected or Synchronized interface or
709          --  (AI-443): Synchronized formal derived type declaration.
710
711          when Tok_Protected    |
712               Tok_Synchronized |
713               Tok_Task         =>
714
715             declare
716                Saved_Token : constant Token_Type := Token;
717
718             begin
719                Scan; -- past TASK, PROTECTED or SYNCHRONIZED
720
721                --  Synchronized derived type
722
723                if Token = Tok_New then
724                   Typedef_Node := P_Formal_Derived_Type_Definition;
725
726                   if Saved_Token = Tok_Synchronized then
727                      Set_Synchronized_Present (Typedef_Node);
728                   else
729                      Error_Msg_SC ("invalid kind of formal derived type");
730                   end if;
731
732                --  Interface
733
734                else
735                   Typedef_Node :=
736                     P_Interface_Type_Definition (Abstract_Present => False);
737
738                   case Saved_Token is
739                      when Tok_Task =>
740                         Set_Task_Present         (Typedef_Node);
741
742                      when Tok_Protected =>
743                         Set_Protected_Present    (Typedef_Node);
744
745                      when Tok_Synchronized =>
746                         Set_Synchronized_Present (Typedef_Node);
747
748                      when others =>
749                         null;
750                   end case;
751                end if;
752
753                return Typedef_Node;
754             end;
755
756          when others =>
757             Error_Msg_BC ("expecting generic type definition here");
758             Resync_Past_Semicolon;
759             return Error;
760
761       end case;
762    end P_Formal_Type_Definition;
763
764    --------------------------------------------
765    -- 12.5.1  Formal Private Type Definition --
766    --------------------------------------------
767
768    --  FORMAL_PRIVATE_TYPE_DEFINITION ::=
769    --    [[abstract] tagged] [limited] private
770
771    --  The caller has checked the initial token is PRIVATE, ABSTRACT,
772    --   TAGGED or LIMITED
773
774    --  Error recovery: cannot raise Error_Resync
775
776    function P_Formal_Private_Type_Definition return Node_Id is
777       Def_Node : Node_Id;
778
779    begin
780       Def_Node := New_Node (N_Formal_Private_Type_Definition, Token_Ptr);
781
782       if Token = Tok_Abstract then
783          Scan; -- past ABSTRACT
784
785          if Token_Name = Name_Tagged then
786             Check_95_Keyword (Tok_Tagged, Tok_Private);
787             Check_95_Keyword (Tok_Tagged, Tok_Limited);
788          end if;
789
790          if Token /= Tok_Tagged then
791             Error_Msg_SP ("ABSTRACT must be followed by TAGGED");
792          else
793             Set_Abstract_Present (Def_Node, True);
794          end if;
795       end if;
796
797       if Token = Tok_Tagged then
798          Set_Tagged_Present (Def_Node, True);
799          Scan; -- past TAGGED
800       end if;
801
802       if Token = Tok_Limited then
803          Set_Limited_Present (Def_Node, True);
804          Scan; -- past LIMITED
805       end if;
806
807       if Token = Tok_Abstract then
808          if Prev_Token = Tok_Tagged then
809             Error_Msg_SC ("ABSTRACT must come before TAGGED");
810          elsif Prev_Token = Tok_Limited then
811             Error_Msg_SC ("ABSTRACT must come before LIMITED");
812          end if;
813
814          Resync_Past_Semicolon;
815
816       elsif Token = Tok_Tagged then
817          Error_Msg_SC ("TAGGED must come before LIMITED");
818          Resync_Past_Semicolon;
819       end if;
820
821       Set_Sloc (Def_Node, Token_Ptr);
822       T_Private;
823       return Def_Node;
824    end P_Formal_Private_Type_Definition;
825
826    --------------------------------------------
827    -- 12.5.1  Formal Derived Type Definition --
828    --------------------------------------------
829
830    --  FORMAL_DERIVED_TYPE_DEFINITION ::=
831    --    [abstract] [limited | synchronized]
832    --         new SUBTYPE_MARK [[and INTERFACE_LIST] with private]
833
834    --  The caller has checked the initial token(s) is/are NEW, ASTRACT NEW,
835    --  or LIMITED NEW, ABSTRACT LIMITED NEW, SYNCHRONIZED NEW or ABSTRACT
836    --  SYNCHRONIZED NEW.
837
838    --  Error recovery: cannot raise Error_Resync
839
840    function P_Formal_Derived_Type_Definition return Node_Id is
841       Def_Node : Node_Id;
842
843    begin
844       Def_Node := New_Node (N_Formal_Derived_Type_Definition, Token_Ptr);
845
846       if Token = Tok_Abstract then
847          Set_Abstract_Present (Def_Node);
848          Scan; -- past ABSTRACT
849       end if;
850
851       if Token = Tok_Limited then
852          Set_Limited_Present (Def_Node);
853          Scan;  --  past LIMITED
854
855          if Ada_Version < Ada_05 then
856             Error_Msg_SP
857               ("LIMITED in derived type is an Ada 2005 extension");
858             Error_Msg_SP
859               ("\unit must be compiled with -gnat05 switch");
860          end if;
861
862       elsif Token = Tok_Synchronized then
863          Set_Synchronized_Present (Def_Node);
864          Scan;  --  past SYNCHRONIZED
865
866          if Ada_Version < Ada_05 then
867             Error_Msg_SP
868               ("SYNCHRONIZED in derived type is an Ada 2005 extension");
869             Error_Msg_SP
870               ("\unit must be compiled with -gnat05 switch");
871          end if;
872       end if;
873
874       if Token = Tok_Abstract then
875          Scan;  --  past ABSTRACT, diagnosed already in caller.
876       end if;
877
878       Scan; -- past NEW;
879       Set_Subtype_Mark (Def_Node, P_Subtype_Mark);
880       No_Constraint;
881
882       --  Ada 2005 (AI-251): Deal with interfaces
883
884       if Token = Tok_And then
885          Scan; -- past AND
886
887          if Ada_Version < Ada_05 then
888             Error_Msg_SP
889               ("abstract interface is an Ada 2005 extension");
890             Error_Msg_SP ("\unit must be compiled with -gnat05 switch");
891          end if;
892
893          Set_Interface_List (Def_Node, New_List);
894
895          loop
896             Append (P_Qualified_Simple_Name, Interface_List (Def_Node));
897             exit when Token /= Tok_And;
898             Scan; -- past AND
899          end loop;
900       end if;
901
902       if Token = Tok_With then
903          Scan; -- past WITH
904          Set_Private_Present (Def_Node, True);
905          T_Private;
906
907       elsif Token = Tok_Tagged then
908          Scan;
909
910          if Token = Tok_Private then
911             Error_Msg_SC ("TAGGED should be WITH");
912             Set_Private_Present (Def_Node, True);
913             T_Private;
914          else
915             Ignore (Tok_Tagged);
916          end if;
917       end if;
918
919       return Def_Node;
920    end P_Formal_Derived_Type_Definition;
921
922    ---------------------------------------------
923    -- 12.5.2  Formal Discrete Type Definition --
924    ---------------------------------------------
925
926    --  FORMAL_DISCRETE_TYPE_DEFINITION ::= (<>)
927
928    --  The caller has checked the initial token is left paren
929
930    --  Error recovery: cannot raise Error_Resync
931
932    function P_Formal_Discrete_Type_Definition return Node_Id is
933       Def_Node : Node_Id;
934
935    begin
936       Def_Node := New_Node (N_Formal_Discrete_Type_Definition, Token_Ptr);
937       Scan; -- past left paren
938       T_Box;
939       T_Right_Paren;
940       return Def_Node;
941    end P_Formal_Discrete_Type_Definition;
942
943    ---------------------------------------------------
944    -- 12.5.2  Formal Signed Integer Type Definition --
945    ---------------------------------------------------
946
947    --  FORMAL_SIGNED_INTEGER_TYPE_DEFINITION ::= range <>
948
949    --  The caller has checked the initial token is RANGE
950
951    --  Error recovery: cannot raise Error_Resync
952
953    function P_Formal_Signed_Integer_Type_Definition return Node_Id is
954       Def_Node : Node_Id;
955
956    begin
957       Def_Node :=
958         New_Node (N_Formal_Signed_Integer_Type_Definition, Token_Ptr);
959       Scan; -- past RANGE
960       T_Box;
961       return Def_Node;
962    end P_Formal_Signed_Integer_Type_Definition;
963
964    --------------------------------------------
965    -- 12.5.2  Formal Modular Type Definition --
966    --------------------------------------------
967
968    --  FORMAL_MODULAR_TYPE_DEFINITION ::= mod <>
969
970    --  The caller has checked the initial token is MOD
971
972    --  Error recovery: cannot raise Error_Resync
973
974    function P_Formal_Modular_Type_Definition return Node_Id is
975       Def_Node : Node_Id;
976
977    begin
978       Def_Node :=
979         New_Node (N_Formal_Modular_Type_Definition, Token_Ptr);
980       Scan; -- past MOD
981       T_Box;
982       return Def_Node;
983    end P_Formal_Modular_Type_Definition;
984
985    ----------------------------------------------
986    -- 12.5.2  Formal Floating Point Definition --
987    ----------------------------------------------
988
989    --  FORMAL_FLOATING_POINT_DEFINITION ::= digits <>
990
991    --  The caller has checked the initial token is DIGITS
992
993    --  Error recovery: cannot raise Error_Resync
994
995    function P_Formal_Floating_Point_Definition return Node_Id is
996       Def_Node : Node_Id;
997
998    begin
999       Def_Node :=
1000         New_Node (N_Formal_Floating_Point_Definition, Token_Ptr);
1001       Scan; -- past DIGITS
1002       T_Box;
1003       return Def_Node;
1004    end P_Formal_Floating_Point_Definition;
1005
1006    -------------------------------------------
1007    -- 12.5.2  Formal Fixed Point Definition --
1008    -------------------------------------------
1009
1010    --  This routine parses either a formal ordinary fixed point definition
1011    --  or a formal decimal fixed point definition:
1012
1013    --  FORMAL_ORDINARY_FIXED_POINT_DEFINITION ::= delta <>
1014
1015    --  FORMAL_DECIMAL_FIXED_POINT_DEFINITION ::= delta <> digits <>
1016
1017    --  The caller has checked the initial token is DELTA
1018
1019    --  Error recovery: cannot raise Error_Resync
1020
1021    function P_Formal_Fixed_Point_Definition return Node_Id is
1022       Def_Node   : Node_Id;
1023       Delta_Sloc : Source_Ptr;
1024
1025    begin
1026       Delta_Sloc := Token_Ptr;
1027       Scan; -- past DELTA
1028       T_Box;
1029
1030       if Token = Tok_Digits then
1031          Def_Node :=
1032            New_Node (N_Formal_Decimal_Fixed_Point_Definition, Delta_Sloc);
1033          Scan; -- past DIGITS
1034          T_Box;
1035       else
1036          Def_Node :=
1037            New_Node (N_Formal_Ordinary_Fixed_Point_Definition, Delta_Sloc);
1038       end if;
1039
1040       return Def_Node;
1041    end P_Formal_Fixed_Point_Definition;
1042
1043    ----------------------------------------------------
1044    -- 12.5.2  Formal Ordinary Fixed Point Definition --
1045    ----------------------------------------------------
1046
1047    --  Parsed by P_Formal_Fixed_Point_Definition (12.5.2)
1048
1049    ---------------------------------------------------
1050    -- 12.5.2  Formal Decimal Fixed Point Definition --
1051    ---------------------------------------------------
1052
1053    --  Parsed by P_Formal_Fixed_Point_Definition (12.5.2)
1054
1055    ------------------------------------------
1056    -- 12.5.3  Formal Array Type Definition --
1057    ------------------------------------------
1058
1059    --  Parsed by P_Formal_Type_Definition (12.5)
1060
1061    -------------------------------------------
1062    -- 12.5.4  Formal Access Type Definition --
1063    -------------------------------------------
1064
1065    --  Parsed by P_Formal_Type_Definition (12.5)
1066
1067    -----------------------------------------
1068    -- 12.6  Formal Subprogram Declaration --
1069    -----------------------------------------
1070
1071    --  FORMAL_SUBPROGRAM_DECLARATION ::=
1072    --    FORMAL_CONCRETE_SUBPROGRAM_DECLARATION
1073    --  | FORMAL_ABSTRACT_SUBPROGRAM_DECLARATION
1074
1075    --  FORMAL_CONCRETE_SUBPROGRAM_DECLARATION ::=
1076    --    with SUBPROGRAM_SPECIFICATION [is SUBPROGRAM_DEFAULT];
1077
1078    --  FORMAL_ABSTRACT_SUBPROGRAM_DECLARATION ::=
1079    --    with SUBPROGRAM_SPECIFICATION is abstract [SUBPROGRAM_DEFAULT];
1080
1081    --  SUBPROGRAM_DEFAULT ::= DEFAULT_NAME | <>
1082
1083    --  DEFAULT_NAME ::= NAME | null
1084
1085    --  The caller has checked that the initial tokens are WITH FUNCTION or
1086    --  WITH PROCEDURE, and the initial WITH has been scanned out.
1087
1088    --  A null default is an Ada 2005 feature
1089
1090    --  Error recovery: cannot raise Error_Resync
1091
1092    function P_Formal_Subprogram_Declaration return Node_Id is
1093       Prev_Sloc : constant Source_Ptr := Prev_Token_Ptr;
1094       Spec_Node : constant Node_Id    := P_Subprogram_Specification;
1095       Def_Node  : Node_Id;
1096
1097    begin
1098       if Token = Tok_Is then
1099          T_Is; -- past IS, skip extra IS or ";"
1100
1101          if Token = Tok_Abstract then
1102             Def_Node :=
1103               New_Node (N_Formal_Abstract_Subprogram_Declaration, Prev_Sloc);
1104             Scan; -- past ABSTRACT
1105
1106             if Ada_Version < Ada_05 then
1107                Error_Msg_SP
1108                  ("formal abstract subprograms are an Ada 2005 extension");
1109                Error_Msg_SP ("\unit must be compiled with -gnat05 switch");
1110             end if;
1111
1112          else
1113             Def_Node :=
1114               New_Node (N_Formal_Concrete_Subprogram_Declaration, Prev_Sloc);
1115          end if;
1116
1117          Set_Specification (Def_Node, Spec_Node);
1118
1119          if Token = Tok_Semicolon then
1120             Scan; -- past ";"
1121
1122          elsif Token = Tok_Box then
1123             Set_Box_Present (Def_Node, True);
1124             Scan; -- past <>
1125             T_Semicolon;
1126
1127          elsif Token = Tok_Null then
1128             if Ada_Version < Ada_05 then
1129                Error_Msg_SP
1130                  ("null default subprograms are an Ada 2005 extension");
1131                Error_Msg_SP ("\unit must be compiled with -gnat05 switch");
1132             end if;
1133
1134             if Nkind (Spec_Node) = N_Procedure_Specification then
1135                Set_Null_Present (Spec_Node);
1136             else
1137                Error_Msg_SP ("only procedures can be null");
1138             end if;
1139
1140             Scan;  --  past NULL
1141             T_Semicolon;
1142
1143          else
1144             Set_Default_Name (Def_Node, P_Name);
1145             T_Semicolon;
1146          end if;
1147
1148       else
1149          Def_Node :=
1150            New_Node (N_Formal_Concrete_Subprogram_Declaration, Prev_Sloc);
1151          Set_Specification (Def_Node, Spec_Node);
1152          T_Semicolon;
1153       end if;
1154
1155       return Def_Node;
1156    end P_Formal_Subprogram_Declaration;
1157
1158    ------------------------------
1159    -- 12.6  Subprogram Default --
1160    ------------------------------
1161
1162    --  Parsed by P_Formal_Procedure_Declaration (12.6)
1163
1164    ------------------------
1165    -- 12.6  Default Name --
1166    ------------------------
1167
1168    --  Parsed by P_Formal_Procedure_Declaration (12.6)
1169
1170    --------------------------------------
1171    -- 12.7  Formal Package Declaration --
1172    --------------------------------------
1173
1174    --  FORMAL_PACKAGE_DECLARATION ::=
1175    --    with package DEFINING_IDENTIFIER
1176    --      is new generic_package_NAME FORMAL_PACKAGE_ACTUAL_PART;
1177
1178    --  FORMAL_PACKAGE_ACTUAL_PART ::=
1179    --    ([OTHERS =>] <>) |
1180    --    [GENERIC_ACTUAL_PART]
1181    --    (FORMAL_PACKAGE_ASSOCIATION {, FORMAL_PACKAGE_ASSOCIATION}
1182    --      [, OTHERS => <>)
1183
1184    --  FORMAL_PACKAGE_ASSOCIATION ::=
1185    --    GENERIC_ASSOCIATION
1186    --    | GENERIC_FORMAL_PARAMETER_SELECTOR_NAME => <>
1187
1188    --  The caller has checked that the initial tokens are WITH PACKAGE,
1189    --  and the initial WITH has been scanned out (so Token = Tok_Package).
1190
1191    --  Error recovery: cannot raise Error_Resync
1192
1193    function P_Formal_Package_Declaration return Node_Id is
1194       Def_Node : Node_Id;
1195       Scan_State : Saved_Scan_State;
1196
1197    begin
1198       Def_Node := New_Node (N_Formal_Package_Declaration, Prev_Token_Ptr);
1199       Scan; -- past PACKAGE
1200       Set_Defining_Identifier (Def_Node, P_Defining_Identifier (C_Is));
1201       T_Is;
1202       T_New;
1203       Set_Name (Def_Node, P_Qualified_Simple_Name);
1204
1205       if Token = Tok_Left_Paren then
1206          Save_Scan_State (Scan_State); -- at the left paren
1207          Scan; -- past the left paren
1208
1209          if Token = Tok_Box then
1210             Set_Box_Present (Def_Node, True);
1211             Scan; -- past box
1212             T_Right_Paren;
1213
1214          else
1215             Restore_Scan_State (Scan_State); -- to the left paren
1216             Set_Generic_Associations (Def_Node, P_Generic_Actual_Part_Opt);
1217          end if;
1218       end if;
1219
1220       T_Semicolon;
1221       return Def_Node;
1222    end P_Formal_Package_Declaration;
1223
1224    --------------------------------------
1225    -- 12.7  Formal Package Actual Part --
1226    --------------------------------------
1227
1228    --  Parsed by P_Formal_Package_Declaration (12.7)
1229
1230 end Ch12;