OSDN Git Service

* sysdep.c: Problem discovered during IA64 VMS port.
[pf3gnuchains/gcc-fork.git] / gcc / ada / treeprs.ads
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                              T R E E P R S                               --
6 --                                                                          --
7 --                                 S p e c                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2003 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,  59 Temple Place - Suite 330,  Boston, --
20 -- MA 02111-1307, 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
28 --  This package contains the declaration of the string used by the Tree_Print
29 --  package. It must be updated whenever the arrangements of the field names
30 --  in package Sinfo is changed. The utility program XTREEPRS is used to
31 --  do this update correctly using the template treeprs.adt as input.
32
33 with Sinfo; use Sinfo;
34
35 package Treeprs is
36
37    --------------------------------
38    -- String Data for Node Print --
39    --------------------------------
40
41    --  String data for print out. The Pchars array is a long string with the
42    --  the entry for each node type consisting of a single blank, followed by
43    --  a series of entries, one for each Op or Flag field used for the node.
44    --  Each entry has a single character which identifies the field, followed
45    --  by the synonym name. The starting location for a given node type is
46    --  found from the corresponding entry in the Pchars_Pos_Array.
47
48    --  The following characters identify the field. These are characters
49    --  which  could never occur in a field name, so they also mark the
50    --  end of the previous name.
51
52    subtype Fchar is Character range '#' .. '9';
53
54    F_Field1     : constant Fchar := '#'; -- Character'Val (16#23#)
55    F_Field2     : constant Fchar := '$'; -- Character'Val (16#24#)
56    F_Field3     : constant Fchar := '%'; -- Character'Val (16#25#)
57    F_Field4     : constant Fchar := '&'; -- Character'Val (16#26#)
58    F_Field5     : constant Fchar := '''; -- Character'Val (16#27#)
59    F_Flag1      : constant Fchar := '('; -- Character'Val (16#28#)
60    F_Flag2      : constant Fchar := ')'; -- Character'Val (16#29#)
61    F_Flag3      : constant Fchar := '*'; -- Character'Val (16#2A#)
62    F_Flag4      : constant Fchar := '+'; -- Character'Val (16#2B#)
63    F_Flag5      : constant Fchar := ','; -- Character'Val (16#2C#)
64    F_Flag6      : constant Fchar := '-'; -- Character'Val (16#2D#)
65    F_Flag7      : constant Fchar := '.'; -- Character'Val (16#2E#)
66    F_Flag8      : constant Fchar := '/'; -- Character'Val (16#2F#)
67    F_Flag9      : constant Fchar := '0'; -- Character'Val (16#30#)
68    F_Flag10     : constant Fchar := '1'; -- Character'Val (16#31#)
69    F_Flag11     : constant Fchar := '2'; -- Character'Val (16#32#)
70    F_Flag12     : constant Fchar := '3'; -- Character'Val (16#33#)
71    F_Flag13     : constant Fchar := '4'; -- Character'Val (16#34#)
72    F_Flag14     : constant Fchar := '5'; -- Character'Val (16#35#)
73    F_Flag15     : constant Fchar := '6'; -- Character'Val (16#36#)
74    F_Flag16     : constant Fchar := '7'; -- Character'Val (16#37#)
75    F_Flag17     : constant Fchar := '8'; -- Character'Val (16#38#)
76    F_Flag18     : constant Fchar := '9'; -- Character'Val (16#39#)
77
78    --  Note this table does not include entity field and flags whose access
79    --  functions are in Einfo (these are handled by the Print_Entity_Info
80    --  procedure in Treepr, which uses the routines in Einfo to get the
81    --  proper symbolic information). In addition, the following fields are
82    --  handled by Treepr, and do not appear in the Pchars array:
83
84    --    Analyzed
85    --    Cannot_Be_Constant
86    --    Chars
87    --    Comes_From_Source
88    --    Error_Posted
89    --    Etype
90    --    Is_Controlling_Actual
91    --    Is_Overloaded
92    --    Is_Static_Expression
93    --    Left_Opnd
94    --    Must_Check_Expr
95    --    Must_Not_Freeze
96    --    No_Overflow_Expr
97    --    Paren_Count
98    --    Raises_Constraint_Error
99    --    Right_Opnd
100
101    Pchars : constant String :=
102       --  Unused_At_Start
103       "" &
104       --  At_Clause
105       "#Identifier%Expression" &
106       --  Component_Clause
107       "#Component_Name$Position%First_Bit&Last_Bit" &
108       --  Enumeration_Representation_Clause
109       "#Identifier%Array_Aggregate&Next_Rep_Item" &
110       --  Mod_Clause
111       "%Expression&Pragmas_Before" &
112       --  Record_Representation_Clause
113       "#Identifier$Mod_Clause%Component_Clauses&Next_Rep_Item" &
114       --  Attribute_Definition_Clause
115       "$Name%Expression&Next_Rep_Item+From_At_Mod2Check_Address_Alignment" &
116       --  Empty
117       "" &
118       --  Pragma
119       "$Pragma_Argument_Associations%Debug_Statement&Next_Rep_Item" &
120       --  Pragma_Argument_Association
121       "%Expression" &
122       --  Error
123       "" &
124       --  Defining_Character_Literal
125       "$Next_Entity%Scope" &
126       --  Defining_Identifier
127       "$Next_Entity%Scope" &
128       --  Defining_Operator_Symbol
129       "$Next_Entity%Scope" &
130       --  Expanded_Name
131       "%Prefix$Selector_Name&Entity&Associated_Node4Redundant_Use2Has_Privat" &
132          "e_View" &
133       --  Identifier
134       "&Entity&Associated_Node$Original_Discriminant4Redundant_Use2Has_Priva" &
135          "te_View" &
136       --  Operator_Symbol
137       "%Strval&Entity&Associated_Node2Has_Private_View" &
138       --  Character_Literal
139       "$Char_Literal_Value&Entity&Associated_Node2Has_Private_View" &
140       --  Op_Add
141       "" &
142       --  Op_Concat
143       "4Is_Component_Left_Opnd5Is_Component_Right_Opnd" &
144       --  Op_Expon
145       "4Is_Power_Of_2_For_Shift" &
146       --  Op_Subtract
147       "" &
148       --  Op_Divide
149       "5Treat_Fixed_As_Integer4Do_Division_Check9Rounded_Result" &
150       --  Op_Mod
151       "5Treat_Fixed_As_Integer4Do_Division_Check" &
152       --  Op_Multiply
153       "5Treat_Fixed_As_Integer9Rounded_Result" &
154       --  Op_Rem
155       "5Treat_Fixed_As_Integer4Do_Division_Check" &
156       --  Op_And
157       "+Do_Length_Check" &
158       --  Op_Eq
159       "" &
160       --  Op_Ge
161       "" &
162       --  Op_Gt
163       "" &
164       --  Op_Le
165       "" &
166       --  Op_Lt
167       "" &
168       --  Op_Ne
169       "" &
170       --  Op_Or
171       "+Do_Length_Check" &
172       --  Op_Xor
173       "+Do_Length_Check" &
174       --  Op_Rotate_Left
175       "+Shift_Count_OK" &
176       --  Op_Rotate_Right
177       "+Shift_Count_OK" &
178       --  Op_Shift_Left
179       "+Shift_Count_OK" &
180       --  Op_Shift_Right
181       "+Shift_Count_OK" &
182       --  Op_Shift_Right_Arithmetic
183       "+Shift_Count_OK" &
184       --  Op_Abs
185       "" &
186       --  Op_Minus
187       "" &
188       --  Op_Not
189       "" &
190       --  Op_Plus
191       "" &
192       --  Attribute_Reference
193       "%Prefix$Attribute_Name#Expressions&Entity&Associated_Node8Do_Overflow" &
194          "_Check4Redundant_Use+OK_For_Stream5Must_Be_Byte_Aligned" &
195       --  And_Then
196       "#Actions" &
197       --  Conditional_Expression
198       "#Expressions$Then_Actions%Else_Actions" &
199       --  Explicit_Dereference
200       "%Prefix" &
201       --  Function_Call
202       "$Name%Parameter_Associations&First_Named_Actual#Controlling_Argument4" &
203          "Do_Tag_Check8Parameter_List_Truncated9ABE_Is_Certain" &
204       --  In
205       "" &
206       --  Indexed_Component
207       "%Prefix#Expressions" &
208       --  Integer_Literal
209       "$Original_Entity%Intval4Print_In_Hex" &
210       --  Not_In
211       "" &
212       --  Null
213       "" &
214       --  Or_Else
215       "#Actions" &
216       --  Procedure_Call_Statement
217       "$Name%Parameter_Associations&First_Named_Actual#Controlling_Argument4" &
218          "Do_Tag_Check8Parameter_List_Truncated9ABE_Is_Certain" &
219       --  Qualified_Expression
220       "&Subtype_Mark%Expression" &
221       --  Raise_Constraint_Error
222       "#Condition%Reason" &
223       --  Raise_Program_Error
224       "#Condition%Reason" &
225       --  Raise_Storage_Error
226       "#Condition%Reason" &
227       --  Aggregate
228       "#Expressions$Component_Associations8Null_Record_Present%Aggregate_Bou" &
229          "nds&Associated_Node+Static_Processing_OK9Compile_Time_Known_Aggreg" &
230          "ate2Expansion_Delayed" &
231       --  Allocator
232       "%Expression#Storage_Pool&Procedure_To_Call4No_Initialization8Do_Stora" &
233          "ge_Check" &
234       --  Extension_Aggregate
235       "%Ancestor_Part&Associated_Node#Expressions$Component_Associations8Nul" &
236          "l_Record_Present2Expansion_Delayed" &
237       --  Range
238       "#Low_Bound$High_Bound2Includes_Infinities" &
239       --  Real_Literal
240       "$Original_Entity%Realval&Corresponding_Integer_Value2Is_Machine_Numbe" &
241          "r" &
242       --  Reference
243       "%Prefix" &
244       --  Selected_Component
245       "%Prefix$Selector_Name&Associated_Node4Do_Discriminant_Check2Is_In_Dis" &
246          "criminant_Check" &
247       --  Slice
248       "%Prefix&Discrete_Range" &
249       --  String_Literal
250       "%Strval2Has_Wide_Character" &
251       --  Subprogram_Info
252       "#Identifier" &
253       --  Type_Conversion
254       "&Subtype_Mark%Expression4Do_Tag_Check+Do_Length_Check8Do_Overflow_Che" &
255          "ck2Float_Truncate9Rounded_Result5Conversion_OK" &
256       --  Unchecked_Expression
257       "%Expression" &
258       --  Unchecked_Type_Conversion
259       "&Subtype_Mark%Expression2Kill_Range_Check8No_Truncation" &
260       --  Subtype_Indication
261       "&Subtype_Mark%Constraint/Must_Not_Freeze" &
262       --  Component_Declaration
263       "#Defining_Identifier+Aliased_Present'Subtype_Indication%Expression,Mo" &
264          "re_Ids-Prev_Ids" &
265       --  Entry_Declaration
266       "#Defining_Identifier&Discrete_Subtype_Definition%Parameter_Specificat" &
267          "ions'Corresponding_Body" &
268       --  Formal_Object_Declaration
269       "#Defining_Identifier6In_Present8Out_Present&Subtype_Mark%Expression,M" &
270          "ore_Ids-Prev_Ids" &
271       --  Formal_Type_Declaration
272       "#Defining_Identifier%Formal_Type_Definition&Discriminant_Specificatio" &
273          "ns4Unknown_Discriminants_Present" &
274       --  Full_Type_Declaration
275       "#Defining_Identifier&Discriminant_Specifications%Type_Definition2Disc" &
276          "r_Check_Funcs_Built" &
277       --  Incomplete_Type_Declaration
278       "#Defining_Identifier&Discriminant_Specifications4Unknown_Discriminant" &
279          "s_Present" &
280       --  Loop_Parameter_Specification
281       "#Defining_Identifier6Reverse_Present&Discrete_Subtype_Definition" &
282       --  Object_Declaration
283       "#Defining_Identifier+Aliased_Present8Constant_Present&Object_Definiti" &
284          "on%Expression$Handler_List_Entry'Corresponding_Generic_Association" &
285          ",More_Ids-Prev_Ids4No_Initialization6Assignment_OK2Exception_Junk5" &
286          "Delay_Finalize_Attach7Is_Subprogram_Descriptor" &
287       --  Protected_Type_Declaration
288       "#Defining_Identifier&Discriminant_Specifications%Protected_Definition" &
289          "'Corresponding_Body" &
290       --  Private_Extension_Declaration
291       "#Defining_Identifier&Discriminant_Specifications4Unknown_Discriminant" &
292          "s_Present+Abstract_Present'Subtype_Indication" &
293       --  Private_Type_Declaration
294       "#Defining_Identifier&Discriminant_Specifications4Unknown_Discriminant" &
295          "s_Present+Abstract_Present6Tagged_Present8Limited_Present" &
296       --  Subtype_Declaration
297       "#Defining_Identifier'Subtype_Indication&Generic_Parent_Type2Exception" &
298          "_Junk" &
299       --  Function_Specification
300       "#Defining_Unit_Name$Elaboration_Boolean%Parameter_Specifications&Subt" &
301          "ype_Mark'Generic_Parent" &
302       --  Procedure_Specification
303       "#Defining_Unit_Name$Elaboration_Boolean%Parameter_Specifications'Gene" &
304          "ric_Parent" &
305       --  Entry_Index_Specification
306       "#Defining_Identifier&Discrete_Subtype_Definition" &
307       --  Freeze_Entity
308       "&Entity$Access_Types_To_Process%TSS_Elist#Actions'First_Subtype_Link" &
309       --  Access_Function_Definition
310       "6Protected_Present%Parameter_Specifications&Subtype_Mark" &
311       --  Access_Procedure_Definition
312       "6Protected_Present%Parameter_Specifications" &
313       --  Task_Type_Declaration
314       "#Defining_Identifier$Task_Body_Procedure&Discriminant_Specifications%" &
315          "Task_Definition'Corresponding_Body" &
316       --  Package_Body_Stub
317       "#Defining_Identifier&Library_Unit'Corresponding_Body" &
318       --  Protected_Body_Stub
319       "#Defining_Identifier&Library_Unit'Corresponding_Body" &
320       --  Subprogram_Body_Stub
321       "#Specification&Library_Unit'Corresponding_Body" &
322       --  Task_Body_Stub
323       "#Defining_Identifier&Library_Unit'Corresponding_Body" &
324       --  Function_Instantiation
325       "#Defining_Unit_Name$Name%Generic_Associations&Parent_Spec'Instance_Sp" &
326          "ec9ABE_Is_Certain" &
327       --  Package_Instantiation
328       "#Defining_Unit_Name$Name%Generic_Associations&Parent_Spec'Instance_Sp" &
329          "ec9ABE_Is_Certain" &
330       --  Procedure_Instantiation
331       "#Defining_Unit_Name$Name&Parent_Spec%Generic_Associations'Instance_Sp" &
332          "ec9ABE_Is_Certain" &
333       --  Package_Body
334       "#Defining_Unit_Name$Declarations&Handled_Statement_Sequence'Correspon" &
335          "ding_Spec4Was_Originally_Stub" &
336       --  Subprogram_Body
337       "#Specification$Declarations&Handled_Statement_Sequence%Activation_Cha" &
338          "in_Entity'Corresponding_Spec+Acts_As_Spec6Bad_Is_Detected8Do_Stora" &
339          "ge_Check-Has_Priority_Pragma.Is_Protected_Subprogram_Body,Is_Task_" &
340          "Master4Was_Originally_Stub" &
341       --  Protected_Body
342       "#Defining_Identifier$Declarations&End_Label'Corresponding_Spec4Was_Or" &
343          "iginally_Stub" &
344       --  Task_Body
345       "#Defining_Identifier$Declarations&Handled_Statement_Sequence,Is_Task_" &
346          "Master%Activation_Chain_Entity'Corresponding_Spec4Was_Originally_S" &
347          "tub" &
348       --  Implicit_Label_Declaration
349       "#Defining_Identifier$Label_Construct" &
350       --  Package_Declaration
351       "#Specification'Corresponding_Body&Parent_Spec%Activation_Chain_Entity" &
352       --  Single_Task_Declaration
353       "#Defining_Identifier%Task_Definition" &
354       --  Subprogram_Declaration
355       "#Specification%Body_To_Inline'Corresponding_Body&Parent_Spec" &
356       --  Use_Package_Clause
357       "$Names%Next_Use_Clause&Hidden_By_Use_Clause" &
358       --  Generic_Package_Declaration
359       "#Specification'Corresponding_Body$Generic_Formal_Declarations&Parent_" &
360          "Spec%Activation_Chain_Entity" &
361       --  Generic_Subprogram_Declaration
362       "#Specification'Corresponding_Body$Generic_Formal_Declarations&Parent_" &
363          "Spec" &
364       --  Constrained_Array_Definition
365       "$Discrete_Subtype_Definitions+Aliased_Present'Subtype_Indication" &
366       --  Unconstrained_Array_Definition
367       "$Subtype_Marks+Aliased_Present'Subtype_Indication" &
368       --  Exception_Renaming_Declaration
369       "#Defining_Identifier$Name" &
370       --  Object_Renaming_Declaration
371       "#Defining_Identifier&Subtype_Mark$Name'Corresponding_Generic_Associat" &
372          "ion" &
373       --  Package_Renaming_Declaration
374       "#Defining_Unit_Name$Name&Parent_Spec" &
375       --  Subprogram_Renaming_Declaration
376       "#Specification$Name&Parent_Spec'Corresponding_Spec" &
377       --  Generic_Function_Renaming_Declaration
378       "#Defining_Unit_Name$Name&Parent_Spec" &
379       --  Generic_Package_Renaming_Declaration
380       "#Defining_Unit_Name$Name&Parent_Spec" &
381       --  Generic_Procedure_Renaming_Declaration
382       "#Defining_Unit_Name$Name&Parent_Spec" &
383       --  Abort_Statement
384       "$Names" &
385       --  Accept_Statement
386       "#Entry_Direct_Name'Entry_Index%Parameter_Specifications&Handled_State" &
387          "ment_Sequence$Declarations" &
388       --  Assignment_Statement
389       "$Name%Expression4Do_Tag_Check+Do_Length_Check,Forwards_OK-Backwards_O" &
390          "K.No_Ctrl_Actions" &
391       --  Asynchronous_Select
392       "#Triggering_Alternative$Abortable_Part" &
393       --  Block_Statement
394       "#Identifier$Declarations&Handled_Statement_Sequence,Is_Task_Master%Ac" &
395          "tivation_Chain_Entity6Has_Created_Identifier-Is_Task_Allocation_Bl" &
396          "ock.Is_Asynchronous_Call_Block" &
397       --  Case_Statement
398       "%Expression&Alternatives'End_Span" &
399       --  Code_Statement
400       "%Expression" &
401       --  Conditional_Entry_Call
402       "#Entry_Call_Alternative&Else_Statements" &
403       --  Delay_Relative_Statement
404       "%Expression" &
405       --  Delay_Until_Statement
406       "%Expression" &
407       --  Entry_Call_Statement
408       "$Name%Parameter_Associations&First_Named_Actual" &
409       --  Free_Statement
410       "%Expression#Storage_Pool&Procedure_To_Call" &
411       --  Goto_Statement
412       "$Name2Exception_Junk" &
413       --  Loop_Statement
414       "#Identifier$Iteration_Scheme%Statements&End_Label6Has_Created_Identif" &
415          "ier7Is_Null_Loop" &
416       --  Null_Statement
417       "" &
418       --  Raise_Statement
419       "$Name" &
420       --  Requeue_Statement
421       "$Name6Abort_Present" &
422       --  Return_Statement
423       "%Expression#Storage_Pool&Procedure_To_Call4Do_Tag_Check$Return_Type,B" &
424          "y_Ref" &
425       --  Selective_Accept
426       "#Select_Alternatives&Else_Statements" &
427       --  Timed_Entry_Call
428       "#Entry_Call_Alternative&Delay_Alternative" &
429       --  Exit_Statement
430       "$Name#Condition" &
431       --  If_Statement
432       "#Condition$Then_Statements%Elsif_Parts&Else_Statements'End_Span" &
433       --  Accept_Alternative
434       "$Accept_Statement#Condition%Statements&Pragmas_Before'Accept_Handler_" &
435          "Records" &
436       --  Delay_Alternative
437       "$Delay_Statement#Condition%Statements&Pragmas_Before" &
438       --  Elsif_Part
439       "#Condition$Then_Statements%Condition_Actions" &
440       --  Entry_Body_Formal_Part
441       "&Entry_Index_Specification%Parameter_Specifications#Condition" &
442       --  Iteration_Scheme
443       "#Condition%Condition_Actions&Loop_Parameter_Specification" &
444       --  Terminate_Alternative
445       "#Condition&Pragmas_Before'Pragmas_After" &
446       --  Abortable_Part
447       "%Statements" &
448       --  Abstract_Subprogram_Declaration
449       "#Specification" &
450       --  Access_Definition
451       "&Subtype_Mark" &
452       --  Access_To_Object_Definition
453       "6All_Present'Subtype_Indication8Constant_Present" &
454       --  Case_Statement_Alternative
455       "&Discrete_Choices%Statements" &
456       --  Compilation_Unit
457       "&Library_Unit#Context_Items6Private_Present$Unit'Aux_Decls_Node8Has_N" &
458          "o_Elaboration_Code4Body_Required+Acts_As_Spec%First_Inlined_Subpro" &
459          "gram" &
460       --  Compilation_Unit_Aux
461       "$Declarations#Actions'Pragmas_After&Config_Pragmas" &
462       --  Component_Association
463       "#Choices$Loop_Actions%Expression" &
464       --  Component_List
465       "%Component_Items&Variant_Part4Null_Present" &
466       --  Derived_Type_Definition
467       "+Abstract_Present'Subtype_Indication%Record_Extension_Part" &
468       --  Decimal_Fixed_Point_Definition
469       "%Delta_Expression$Digits_Expression&Real_Range_Specification" &
470       --  Defining_Program_Unit_Name
471       "$Name#Defining_Identifier" &
472       --  Delta_Constraint
473       "%Delta_Expression&Range_Constraint" &
474       --  Designator
475       "$Name#Identifier" &
476       --  Digits_Constraint
477       "$Digits_Expression&Range_Constraint" &
478       --  Discriminant_Association
479       "#Selector_Names%Expression" &
480       --  Discriminant_Specification
481       "#Defining_Identifier'Discriminant_Type%Expression,More_Ids-Prev_Ids" &
482       --  Enumeration_Type_Definition
483       "#Literals&End_Label" &
484       --  Entry_Body
485       "#Defining_Identifier'Entry_Body_Formal_Part$Declarations&Handled_Stat" &
486          "ement_Sequence%Activation_Chain_Entity" &
487       --  Entry_Call_Alternative
488       "#Entry_Call_Statement%Statements&Pragmas_Before" &
489       --  Exception_Declaration
490       "#Defining_Identifier%Expression,More_Ids-Prev_Ids" &
491       --  Exception_Handler
492       "$Choice_Parameter&Exception_Choices%Statements,Zero_Cost_Handling" &
493       --  Floating_Point_Definition
494       "$Digits_Expression&Real_Range_Specification" &
495       --  Formal_Decimal_Fixed_Point_Definition
496       "" &
497       --  Formal_Derived_Type_Definition
498       "&Subtype_Mark6Private_Present+Abstract_Present" &
499       --  Formal_Discrete_Type_Definition
500       "" &
501       --  Formal_Floating_Point_Definition
502       "" &
503       --  Formal_Modular_Type_Definition
504       "" &
505       --  Formal_Ordinary_Fixed_Point_Definition
506       "" &
507       --  Formal_Package_Declaration
508       "#Defining_Identifier$Name%Generic_Associations6Box_Present'Instance_S" &
509          "pec9ABE_Is_Certain" &
510       --  Formal_Private_Type_Definition
511       "+Abstract_Present6Tagged_Present8Limited_Present" &
512       --  Formal_Signed_Integer_Type_Definition
513       "" &
514       --  Formal_Subprogram_Declaration
515       "#Specification$Default_Name6Box_Present" &
516       --  Generic_Association
517       "$Selector_Name#Explicit_Generic_Actual_Parameter" &
518       --  Handled_Sequence_Of_Statements
519       "%Statements&End_Label'Exception_Handlers#At_End_Proc$First_Real_State" &
520          "ment,Zero_Cost_Handling" &
521       --  Index_Or_Discriminant_Constraint
522       "#Constraints" &
523       --  Itype_Reference
524       "#Itype" &
525       --  Label
526       "#Identifier2Exception_Junk" &
527       --  Modular_Type_Definition
528       "%Expression" &
529       --  Number_Declaration
530       "#Defining_Identifier%Expression,More_Ids-Prev_Ids" &
531       --  Ordinary_Fixed_Point_Definition
532       "%Delta_Expression&Real_Range_Specification" &
533       --  Others_Choice
534       "#Others_Discrete_Choices2All_Others" &
535       --  Package_Specification
536       "#Defining_Unit_Name$Visible_Declarations%Private_Declarations&End_Lab" &
537          "el'Generic_Parent9Limited_View_Installed" &
538       --  Parameter_Association
539       "$Selector_Name%Explicit_Actual_Parameter&Next_Named_Actual" &
540       --  Parameter_Specification
541       "#Defining_Identifier6In_Present8Out_Present$Parameter_Type%Expression" &
542          "4Do_Accessibility_Check,More_Ids-Prev_Ids'Default_Expression" &
543       --  Protected_Definition
544       "$Visible_Declarations%Private_Declarations&End_Label-Has_Priority_Pra" &
545          "gma" &
546       --  Range_Constraint
547       "&Range_Expression" &
548       --  Real_Range_Specification
549       "#Low_Bound$High_Bound" &
550       --  Record_Definition
551       "&End_Label+Abstract_Present6Tagged_Present8Limited_Present#Component_" &
552          "List4Null_Present" &
553       --  Signed_Integer_Type_Definition
554       "#Low_Bound$High_Bound" &
555       --  Single_Protected_Declaration
556       "#Defining_Identifier%Protected_Definition" &
557       --  Subunit
558       "$Name#Proper_Body%Corresponding_Stub" &
559       --  Task_Definition
560       "$Visible_Declarations%Private_Declarations&End_Label-Has_Priority_Pra" &
561          "gma,Has_Storage_Size_Pragma.Has_Task_Info_Pragma/Has_Task_Name_Pra" &
562          "gma" &
563       --  Triggering_Alternative
564       "#Triggering_Statement%Statements&Pragmas_Before" &
565       --  Use_Type_Clause
566       "$Subtype_Marks%Next_Use_Clause&Hidden_By_Use_Clause" &
567       --  Validate_Unchecked_Conversion
568       "#Source_Type$Target_Type" &
569       --  Variant
570       "&Discrete_Choices#Component_List$Enclosing_Variant%Present_Expr'Dchec" &
571          "k_Function" &
572       --  Variant_Part
573       "$Name#Variants" &
574       --  With_Clause
575       "$Name&Library_Unit'Corresponding_Spec,First_Name-Last_Name4Context_In" &
576          "stalled+Elaborate_Present6Elaborate_All_Present7Implicit_With8Limi" &
577          "ted_Present9Limited_View_Installed.Unreferenced_In_Spec/No_Entitie" &
578          "s_Ref_In_Spec" &
579       --  With_Type_Clause
580       "$Name6Tagged_Present" &
581       --  Unused_At_End
582       "";
583
584    type Pchar_Pos_Array is array (Node_Kind) of Positive;
585    Pchar_Pos : constant Pchar_Pos_Array := Pchar_Pos_Array'(
586       N_Unused_At_Start                        => 1,
587       N_At_Clause                              => 1,
588       N_Component_Clause                       => 23,
589       N_Enumeration_Representation_Clause      => 66,
590       N_Mod_Clause                             => 107,
591       N_Record_Representation_Clause           => 133,
592       N_Attribute_Definition_Clause            => 187,
593       N_Empty                                  => 253,
594       N_Pragma                                 => 253,
595       N_Pragma_Argument_Association            => 312,
596       N_Error                                  => 323,
597       N_Defining_Character_Literal             => 323,
598       N_Defining_Identifier                    => 341,
599       N_Defining_Operator_Symbol               => 359,
600       N_Expanded_Name                          => 377,
601       N_Identifier                             => 452,
602       N_Operator_Symbol                        => 528,
603       N_Character_Literal                      => 575,
604       N_Op_Add                                 => 634,
605       N_Op_Concat                              => 634,
606       N_Op_Expon                               => 681,
607       N_Op_Subtract                            => 705,
608       N_Op_Divide                              => 705,
609       N_Op_Mod                                 => 761,
610       N_Op_Multiply                            => 802,
611       N_Op_Rem                                 => 840,
612       N_Op_And                                 => 881,
613       N_Op_Eq                                  => 897,
614       N_Op_Ge                                  => 897,
615       N_Op_Gt                                  => 897,
616       N_Op_Le                                  => 897,
617       N_Op_Lt                                  => 897,
618       N_Op_Ne                                  => 897,
619       N_Op_Or                                  => 897,
620       N_Op_Xor                                 => 913,
621       N_Op_Rotate_Left                         => 929,
622       N_Op_Rotate_Right                        => 944,
623       N_Op_Shift_Left                          => 959,
624       N_Op_Shift_Right                         => 974,
625       N_Op_Shift_Right_Arithmetic              => 989,
626       N_Op_Abs                                 => 1004,
627       N_Op_Minus                               => 1004,
628       N_Op_Not                                 => 1004,
629       N_Op_Plus                                => 1004,
630       N_Attribute_Reference                    => 1004,
631       N_And_Then                               => 1128,
632       N_Conditional_Expression                 => 1136,
633       N_Explicit_Dereference                   => 1174,
634       N_Function_Call                          => 1181,
635       N_In                                     => 1302,
636       N_Indexed_Component                      => 1302,
637       N_Integer_Literal                        => 1321,
638       N_Not_In                                 => 1357,
639       N_Null                                   => 1357,
640       N_Or_Else                                => 1357,
641       N_Procedure_Call_Statement               => 1365,
642       N_Qualified_Expression                   => 1486,
643       N_Raise_Constraint_Error                 => 1510,
644       N_Raise_Program_Error                    => 1527,
645       N_Raise_Storage_Error                    => 1544,
646       N_Aggregate                              => 1561,
647       N_Allocator                              => 1717,
648       N_Extension_Aggregate                    => 1794,
649       N_Range                                  => 1897,
650       N_Real_Literal                           => 1938,
651       N_Reference                              => 2008,
652       N_Selected_Component                     => 2015,
653       N_Slice                                  => 2099,
654       N_String_Literal                         => 2121,
655       N_Subprogram_Info                        => 2147,
656       N_Type_Conversion                        => 2158,
657       N_Unchecked_Expression                   => 2273,
658       N_Unchecked_Type_Conversion              => 2284,
659       N_Subtype_Indication                     => 2339,
660       N_Component_Declaration                  => 2379,
661       N_Entry_Declaration                      => 2463,
662       N_Formal_Object_Declaration              => 2555,
663       N_Formal_Type_Declaration                => 2640,
664       N_Full_Type_Declaration                  => 2741,
665       N_Incomplete_Type_Declaration            => 2829,
666       N_Loop_Parameter_Specification           => 2907,
667       N_Object_Declaration                     => 2971,
668       N_Protected_Type_Declaration             => 3218,
669       N_Private_Extension_Declaration          => 3306,
670       N_Private_Type_Declaration               => 3420,
671       N_Subtype_Declaration                    => 3546,
672       N_Function_Specification                 => 3620,
673       N_Procedure_Specification                => 3712,
674       N_Entry_Index_Specification              => 3791,
675       N_Freeze_Entity                          => 3839,
676       N_Access_Function_Definition             => 3907,
677       N_Access_Procedure_Definition            => 3963,
678       N_Task_Type_Declaration                  => 4006,
679       N_Package_Body_Stub                      => 4109,
680       N_Protected_Body_Stub                    => 4161,
681       N_Subprogram_Body_Stub                   => 4213,
682       N_Task_Body_Stub                         => 4259,
683       N_Function_Instantiation                 => 4311,
684       N_Package_Instantiation                  => 4397,
685       N_Procedure_Instantiation                => 4483,
686       N_Package_Body                           => 4569,
687       N_Subprogram_Body                        => 4667,
688       N_Protected_Body                         => 4894,
689       N_Task_Body                              => 4976,
690       N_Implicit_Label_Declaration             => 5114,
691       N_Package_Declaration                    => 5150,
692       N_Single_Task_Declaration                => 5219,
693       N_Subprogram_Declaration                 => 5255,
694       N_Use_Package_Clause                     => 5315,
695       N_Generic_Package_Declaration            => 5358,
696       N_Generic_Subprogram_Declaration         => 5455,
697       N_Constrained_Array_Definition           => 5528,
698       N_Unconstrained_Array_Definition         => 5592,
699       N_Exception_Renaming_Declaration         => 5641,
700       N_Object_Renaming_Declaration            => 5666,
701       N_Package_Renaming_Declaration           => 5738,
702       N_Subprogram_Renaming_Declaration        => 5774,
703       N_Generic_Function_Renaming_Declaration  => 5824,
704       N_Generic_Package_Renaming_Declaration   => 5860,
705       N_Generic_Procedure_Renaming_Declaration => 5896,
706       N_Abort_Statement                        => 5932,
707       N_Accept_Statement                       => 5938,
708       N_Assignment_Statement                   => 6033,
709       N_Asynchronous_Select                    => 6119,
710       N_Block_Statement                        => 6157,
711       N_Case_Statement                         => 6322,
712       N_Code_Statement                         => 6355,
713       N_Conditional_Entry_Call                 => 6366,
714       N_Delay_Relative_Statement               => 6405,
715       N_Delay_Until_Statement                  => 6416,
716       N_Entry_Call_Statement                   => 6427,
717       N_Free_Statement                         => 6474,
718       N_Goto_Statement                         => 6516,
719       N_Loop_Statement                         => 6536,
720       N_Null_Statement                         => 6621,
721       N_Raise_Statement                        => 6621,
722       N_Requeue_Statement                      => 6626,
723       N_Return_Statement                       => 6645,
724       N_Selective_Accept                       => 6719,
725       N_Timed_Entry_Call                       => 6755,
726       N_Exit_Statement                         => 6796,
727       N_If_Statement                           => 6811,
728       N_Accept_Alternative                     => 6874,
729       N_Delay_Alternative                      => 6950,
730       N_Elsif_Part                             => 7002,
731       N_Entry_Body_Formal_Part                 => 7046,
732       N_Iteration_Scheme                       => 7107,
733       N_Terminate_Alternative                  => 7164,
734       N_Abortable_Part                         => 7203,
735       N_Abstract_Subprogram_Declaration        => 7214,
736       N_Access_Definition                      => 7228,
737       N_Access_To_Object_Definition            => 7241,
738       N_Case_Statement_Alternative             => 7289,
739       N_Compilation_Unit                       => 7317,
740       N_Compilation_Unit_Aux                   => 7456,
741       N_Component_Association                  => 7506,
742       N_Component_List                         => 7538,
743       N_Derived_Type_Definition                => 7580,
744       N_Decimal_Fixed_Point_Definition         => 7638,
745       N_Defining_Program_Unit_Name             => 7698,
746       N_Delta_Constraint                       => 7723,
747       N_Designator                             => 7757,
748       N_Digits_Constraint                      => 7773,
749       N_Discriminant_Association               => 7808,
750       N_Discriminant_Specification             => 7834,
751       N_Enumeration_Type_Definition            => 7901,
752       N_Entry_Body                             => 7920,
753       N_Entry_Call_Alternative                 => 8027,
754       N_Exception_Declaration                  => 8074,
755       N_Exception_Handler                      => 8123,
756       N_Floating_Point_Definition              => 8188,
757       N_Formal_Decimal_Fixed_Point_Definition  => 8231,
758       N_Formal_Derived_Type_Definition         => 8231,
759       N_Formal_Discrete_Type_Definition        => 8277,
760       N_Formal_Floating_Point_Definition       => 8277,
761       N_Formal_Modular_Type_Definition         => 8277,
762       N_Formal_Ordinary_Fixed_Point_Definition => 8277,
763       N_Formal_Package_Declaration             => 8277,
764       N_Formal_Private_Type_Definition         => 8364,
765       N_Formal_Signed_Integer_Type_Definition  => 8412,
766       N_Formal_Subprogram_Declaration          => 8412,
767       N_Generic_Association                    => 8451,
768       N_Handled_Sequence_Of_Statements         => 8499,
769       N_Index_Or_Discriminant_Constraint       => 8591,
770       N_Itype_Reference                        => 8603,
771       N_Label                                  => 8609,
772       N_Modular_Type_Definition                => 8635,
773       N_Number_Declaration                     => 8646,
774       N_Ordinary_Fixed_Point_Definition        => 8695,
775       N_Others_Choice                          => 8737,
776       N_Package_Specification                  => 8772,
777       N_Parameter_Association                  => 8881,
778       N_Parameter_Specification                => 8939,
779       N_Protected_Definition                   => 9068,
780       N_Range_Constraint                       => 9140,
781       N_Real_Range_Specification               => 9157,
782       N_Record_Definition                      => 9178,
783       N_Signed_Integer_Type_Definition         => 9264,
784       N_Single_Protected_Declaration           => 9285,
785       N_Subunit                                => 9326,
786       N_Task_Definition                        => 9362,
787       N_Triggering_Alternative                 => 9500,
788       N_Use_Type_Clause                        => 9547,
789       N_Validate_Unchecked_Conversion          => 9598,
790       N_Variant                                => 9622,
791       N_Variant_Part                           => 9701,
792       N_With_Clause                            => 9715,
793       N_With_Type_Clause                       => 9929,
794       N_Unused_At_End                          => 9949);
795
796 end Treeprs;