home *** CD-ROM | disk | FTP | other *** search
Text File | 1988-05-03 | 284.4 KB | 6,235 lines |
-
- -------- SIMTEL20 Ada Software Repository Prologue ------------
- -- -*
- -- Unit name : Compilation Order Requirements Report
- -- Version : 1.0
- -- Contact : Lt. Colonel Falgiano
- -- : ESD/SCW
- -- : Hanscom AFB, MA 01731
- -- Author : Bill Toscano, Michael Gordon
- -- : Intermetrics, Inc,
- -- : 733 Concord Ave,
- -- : Cambridge, MA 02138
- -- DDN Address :
- -- Copyright : (c) 1985 Intermetrics, Inc.
- -- Date created : 15 October 1985
- -- Release date : 18 March 1985
- -- Last update : 17 March 1985
- -- -*
- ---------------------------------------------------------------
- -- -*
- -- Keywords :
- ----------------:
- --
- -- Abstract : The Compilation Order Requirements Report computes a
- ----------------: proper compilation order for given Ada source files. It
- ----------------: then generates a report showing the computed compilation
- ----------------: order and outputs it to the default output file.
- ----------------:
- ----------------: This tool was developed as a precursor for
- ----------------: the WMCCS Information System (WIS). An
- ----------------: executable version of the tool has been
- ----------------: demonstrated. This source code has sub-
- ----------------: sequently been recompiled but has not under-
- ----------------: gone extensive testing.
- ----------------:
- -- -*
- ------------------ Revision history ---------------------------
- -- -*
- -- DATE VERSION AUTHOR HISTORY
- -- 03/85 1.0 Bill Toscano Initial Release
- -- -*
- ------------------ Distribution and Copyright -----------------
- -- -*
- -- This prologue must be included in all copies of this software.
- --
- -- This software is copyright by the author.
- --
- -- This software is released to the Ada community.
- -- This software is released to the Public Domain (note:
- -- software released to the Public Domain is not subject
- -- to copyright protection).
- -- Restrictions on use or distribution: NONE
- -- -*
- ----------------- Disclaimer ----------------------------------
- -- -*
- -- This software and its documentation are provided "AS IS" and
- -- without any expressed or implied warranties whatsoever.
- --
- -- No warranties as to performance, merchantability, or fitness
- -- for a particular purpose exist.
- --
- -- Because of the diversity of conditions and hardware under
- -- which this software may be used, no warranty of fitness for
- -- a particular purpose is offered. The user is advised to
- -- test the software thoroughly before relying on it. The user
- -- must assume the entire risk and liability of using this
- -- software.
- --
- -- In no event shall any person or organization of people be
- -- held responsible for any direct, indirect, consequential
- -- or inconsequential damages or lost profits.
- -- -*
- ----------------- END-PROLOGUE -------------------------------
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --UNITDAG.SPC
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- with string_pkg;
- package nodes is
-
- type dag_node is record
- name : string_pkg.string_type;
- file : string_pkg.string_type;
- trouble_node : boolean;
- end record;
-
- subtype empty_node is boolean;
-
- end nodes;
-
- with string_pkg;
- package hash is
-
- subtype hash_range is integer range 1..199;
- function hasher(n:string_pkg.string_type) return hash_range;
-
- end hash;
-
- with hashing_functions_pkg;
- package body hash is
-
- function plain_hash is new hashing_functions_pkg.hash_string (hash_range'last);
-
- function hasher(n:string_pkg.string_type) return hash_range is
- begin
- return plain_hash (string_pkg.value (n)) + 1;
- end hasher;
-
- end hash;
-
-
- with string_pkg;
- with dag_pkg;
- with nodes; use nodes;
- with hash; use hash;
- package units_dag_pkg is new dag_pkg (string_pkg.string_type,
- string_pkg.equal,
- dag_node,
- hash_range,
- hasher
- );
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --MINIDAG.SPC
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- with nodes; use nodes;
- with hash; use hash;
- with dag_pkg;
- with string_pkg;
- package mini_dag_pkg is new dag_pkg (string_pkg.string_type,
- string_pkg.equal,
- empty_node,
- hash_range,
- hasher);
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --COPKG.DAT
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
-
- with string_pkg;
- with string_lists;
- with set_pkg;
- with Paginated_Output;
- with ParserDeclarations;
- with units_dag_pkg; use units_dag_pkg;
- with mini_dag_pkg; use mini_dag_pkg;
- with nodes; use nodes;
-
- package compile_order_declarations is
- --| Declarations of objects global to compilation order. Also types
- --| global to compilation order.
-
- --| N/A: Effects, Raises, Requires, Modifies
-
-
- -- package Renames --
-
- package SP renames string_pkg;
- package PD renames ParserDeclarations;
- package id_list_pkg renames string_lists;
-
- -- Exceptions --
-
- duplicate_name : exception; -- raised when there are two lib units
- -- with the same name
-
- -- Types --
-
- type mode_type is (nothing, subp, pkg);
- type prog_type is (spec, bdy, separate_body);
-
- default_empty_node : empty_node := false;
-
- default_node : dag_node := (name => string_pkg.create(""),
- file => string_pkg.create(""),
- trouble_node => false);
-
- subtype units_dag is units_dag_pkg.dag;
- subtype info_dag is mini_dag_pkg.dag;
-
-
-
-
- package id_set_pkg is new set_pkg (string_pkg.string_type,string_pkg.equal);
- subtype id_set is id_set_pkg.set;
-
-
-
- -- Variables --
-
-
- withs_dag : units_dag := units_dag_pkg.create;
- files_dag : info_dag := mini_dag_pkg.create;
- cycle_dag : info_dag := mini_dag_pkg.create;
- withs_list : id_list_pkg.list := id_list_pkg.create;
- unit_list : id_list_pkg.list := id_list_pkg.create;
- name_stack : id_list_pkg.list := id_list_pkg.create;
- prev_token : PD.ParseStackElement;
- unit_name : SP.string_type;
- cu_name : SP.string_type;
- parent_body_name : SP.string_type;
- generic_name : SP.string_type;
- mode : mode_type := nothing;
- unit_type : prog_type;
- current_file : SP.string_type;
- report_file : Paginated_Output.Paginated_File_Handle;
- inline_set : id_set := id_set_pkg.create;
- inline_flag : boolean := false;
- dup_string : SP.string_type;
- dup_file : SP.string_type;
- dummy : SP.string_type; -- dummy for apply actions
-
-
- -- the following is a flag which indicates whether generic instantiations
- -- will produce additional dependencies. The LRM leaves it up to the
- -- implementation to decide how they do generics. In some compilers an
- -- instantiation will create a dependency on the generic's body as well
- -- as its spec. However, some compilers do not create this dependency.
- -- While it would not be wrong to always include this dependency it
- -- would be creating more dependencies and larger graphs and making a
- -- more strict order than absolutely necessary in some cases. So
- -- instead this variable will flag whether to do the dependencies or not.
-
- do_generics : boolean := true;
-
- -- Operations --
- -- debugging procedures
- -- procedure put_dag is new units_dag_pkg.put_image (string_pkg.value);
- -- procedure put_info_dag is new mini_dag_pkg.put_image (string_pkg.value);
-
- end compile_order_declarations;
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --COMPORD.SPC
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- with string_pkg;
- with compile_order_declarations;
-
-
- package Comp_Order is
-
-
-
-
- type report_type is (full, raw, dependency, raw_dependency, compilation,
- raw_compilation, units_order, file_order);
- package COD renames compile_order_declarations;
- package SP renames string_pkg;
-
- internal_error : exception; -- raised when something not normally
- -- caught is raised.
-
- procedure Compilation_Order ( --| Produces a report showing dependencies
- --| and a compilation order for the files input
- Source_List: in --| list of filenames for input
- COD.id_list_pkg.list;
- Output : SP.string_type --| Output file name
- := SP.create("");
- Units_file : SP.string_type --| File containing pairs of file name,
- := SP.create(""); --| unit name for adding to report.
- Which_Report: in --| Indicates whether to write both
- report_type:= full --| tables or just one of them
- );
- --| Raises: FILE_NOT_FOUND
-
- --| Effects:
- --| This tool produces a report showing both withs and withed-by
- --| dependencies between library units for the files in the file_list.
- --| The table names each unit directly withed or withed by the
- --| modules in the input files and also shows a list of everything
- --| indirectly withed or withed by the unit.
- --| The report will also list the library units in their
- --| compilation order. In the compilation list units will be alpha-
- --| betized when order is unimportant, and the dependency report will
- --| show the library units in alphabetical order.
- --| If both tables are to be computed the output will be in a paginated
- --| form for reports. If just one or the other table is asked
- --| for, then the output will be in raw mode which looks basically
- --| the same in format, but the headings will not be present.
- --| If a file in the file list cannot be found FILE_NOT_FOUND is
- --| raised.
-
- --| Modifies: default output
-
- --| N/A: Errors, Requires,
-
- ----------------
-
- end Comp_Order;
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --CDRIVER.ADA
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- with compile_order_declarations;
- with comp_order; use comp_order;
- with command_line_interface;
- with string_pkg; use string_pkg; -- for =
- with file_manager;
- with Text_io;
- with VMS_lib;
-
- procedure compile_order is
-
- package CLI renames command_line_interface;
- package COD renames compile_order_declarations;
- package SP renames string_pkg;
- package FM renames file_manager;
-
- -- Variable Declarations --
-
- output_file : SP.string_type;
- unit_file : SP.string_type;
- source_list : COD.id_list_pkg.list;
- source_files : SP.string_type;
- report_kind : report_type;
- named : CLI.argument_count;
- debug_string : SP.string_type;
- posit : CLI.argument_count;
- arg_array : array (1..4) of sp.string_type :=
- (SP.create (""), SP.create (""), SP.create (""), SP.create ("full"));
- named_array : constant array (1..4) of sp.string_type :=
- (SP.create("Source_List"),
- SP.create ("Output"),
- SP.create ("Units_file"),
- SP.create ("Which_Report"));
- report_string : SP.string_type;
- index : positive;
- max_parm : constant := 4;
-
- procedure parse_sources (input : in out SP.string_type;
- list : in out COD.id_list_pkg.list) is
-
-
- position : natural := 1;
- prev_pos : natural := 1;
- temp_pos : natural := 1;
- output : SP.string_type;
- name : SP.string_type;
- length : natural;
- file_names : COD.id_list_pkg.list;
-
- name_error : exception; -- raised when a name is enclosed by
- -- only one quote
-
- begin
- SP.mark;
- loop
- -- get each element of a comma separated list.
- -- the list must not be empty to start with.
- exit when position = 0;
-
- position := SP.match_c (input, ',', prev_pos);
- -- match the next comma, 0 indicates there isn't one
- if position = 0 then
- name := SP.substr (input,
- prev_pos,
- (SP.length (input)- (prev_pos - 1) ));
- else
- name := SP.substr (input,
- prev_pos,
- position - prev_pos);
- end if;
- length := SP.length (name);
- if SP.equal (SP.substr (name, 1, 1), """") and
- SP.equal (SP.substr (name, length, 1), """") then
- output := output & name & ", ";
- name := SP.substr (name, 2, length-2);
- elsif SP.equal (SP.substr (name, 1, 1), """") or
- SP.equal (SP.substr (name, length, 1), """") then
- raise name_error;
- else
- output := output & """" & name & """, ";
- end if;
- begin
- file_names := FM.expand (name,
- FM.No_Version
- );
- COD.id_list_pkg.Attach (list,
- file_names);
- exception
- when FM.file_not_found =>
- Text_io.Put ("File ");
- Text_io.put (SP.value (name));
- TEXT_IO.PUT_LINE (" does not exist.");
- exit;
- when FM.device_not_ready =>
- Text_io.put ("Device not ready: ");
- Text_io.put_line (SP.value (name));
- exit;
- when FM.directory_not_found =>
- Text_io.put ("Directory not found: ");
- Text_io.put_line (SP.value (name));
- exit;
- when FM.Expand_error | FM.parse_error =>
- Text_io.put ("File name error: ");
- Text_io.put_line (SP.value (name));
- exit;
- end;
- -- skip any spaces after the comma.
- temp_pos := SP.match_not_c (input, ' ', position+1);
- prev_pos := temp_pos;
- end loop;
- input := SP.make_persistent (SP.upper (SP.substr (
- output,
- 1,
- SP.length (output)-2)));
- -- substring because output will always have an extra ', ' on
- -- the end which we want to strip off.
-
- SP.release;
-
- end parse_sources;
-
- procedure put_help is
-
- begin
-
- TEXT_IO.PUT ("-- COMPILE ORDER: produces dependency tables and ");
- Text_io.put_line ("compilation orders for Ada ");
- Text_io.put_line ("-- source files. ");
- Text_io.put_line (" ");
- Text_io.put ("type REPORT_TYPE is (FULL, RAW, DEPENDENCY, ");
- Text_io.put_line ("COMPILATION, RAW_DEPENDENCY, ");
- Text_io.put (" RAW_COMPILATION, UNITS_ORDER");
- Text_io.put_line (", FILE_ORDER);");
- Text_io.put ("type STRING_ARRAY is array (POSITIVE RANGE <>) of ");
- Text_io.put_line ("STRING;");
- Text_io.put_line ("");
- TEXT_IO.PUT_LINE ("procedure COMPILE_ORDER (SOURCE_LIST : in STRING_ARRAY;");
- Text_io.put_line (" OUTPUT : in STRING := """";");
- Text_io.put_line (" UNITS_FILE : in STRING := """";");
- Text_io.put_line (" WHICH_REPORT : in REPORT_TYPE := FULL);");
- Text_io.put_line (" ");
- Text_io.put ("-- SOURCE_LIST specifies the Ada source files for ");
- Text_io.put_line ("analysis. There must be at ");
- Text_io.put_line ("-- least one file. ");
- Text_io.put ("-- OUTPUT specifies the report file (default is ");
- Text_io.put_line ("standard output).");
- Text_io.put ("-- UNITS_FILE specifies the file containing unit and ");
- Text_io.put_line ("corresponding file");
- Text_io.put_line ("-- information. ");
- Text_io.put ("-- WHICH_REPORT indicates the type of report required.");
- Text_io.put_line ("");
- end put_help;
-
-
- begin -- compile_order
- SP.mark;
-
- VMS_lib.set_error;
- CLI.initialize;
-
- named := CLI.Named_arg_count;
- posit := CLI.positional_arg_count;
-
- if (posit > 4) or (posit = 0 and named = 0) or (named > 4)
- or (named + posit > 4) or (named + posit < 1) then
- if not (posit = 0 and named = 0) then
- Text_io.put_line ("Too many paramaters on command line: ");
- end if;
- put_help;
- return;
- else -- there is some combination of the right number of arguments
- for index in 1..posit loop
- arg_array (index) := CLI.Positional_arg_value (index);
- end loop;
- for index in 1..max_parm loop
- arg_array(index) := CLI.Named_arg_value
- (SP.value (named_array(index)),
- arg_array(index));
- end loop;
- CLI.finalize;
- if SP.equal (arg_array(1), "") then
- Text_io.put_line ("No input files: not generating a report");
- return;
- end if;
-
- parse_sources (arg_array (1), source_list);
- output_file := SP.make_persistent (arg_array (2));
- unit_file := SP.make_persistent (arg_array (3));
- report_kind := report_type'VALUE (SP.value (arg_array (4)));
-
- debug_string := arg_array (1);
-
- if not COD.id_list_pkg.IsEmpty (source_list) then
- Text_io.put (" Compile_Order ( Source_List => (");
- Text_io.put_line (SP.value (arg_array(1)) & "),");
- Text_io.put (" Output => """);
- Text_io.put_line (SP.value (output_file) & """,");
- Text_io.put (" Units_File => """);
- Text_io.put_line (SP.value (unit_file) & """,");
- Text_io.put (" Which_Report => ");
- Text_io.put_line (report_type'IMAGE (report_kind) & ");");
- Compilation_Order (Output => output_file,
- Source_list => source_list,
- Units_File => unit_file,
- Which_Report => report_kind);
- else
- Text_io.put_line ("No input files: not generating a report.");
- end if;
-
- end if;
-
- SP.release;
-
- exception
- when CLI.invalid_parameter_order =>
- Text_io.put ("Invalid command line: positional parameters are ");
- Text_io.put_line ("not allowed after ");
- Text_io.put_line (" named parameters");
- put_help;
- when CLI.invalid_named_association =>
- Text_io.put ("Invalid command line: Named parameter is missing");
- text_io.put_line (" a value or a name.");
- put_help;
- when CLI.unreferenced_named_arg =>
- Text_io.put ("Invalid command line: Unknown named parameters ");
- Text_io.put_line ("on command line. ");
- put_help;
- when CLI.missing_positional_arg =>
- Text_io.put ("Invalid command line: Missing a positional");
- Text_io.put_line (" argument on command line");
- put_help;
- when CONSTRAINT_ERROR => -- report_kind is not in report_type
- Text_io.put_line ("Report_Type is unknown. " );
- Text_io.put_line ("Possible values for Report_Type are: ");
- Text_io.put ("FULL, RAW, DEPENDENCY, COMPILATION, RAW_DEPENDENCY");
- Text_io.put_line (", RAW_COMPILATION, UNITS_ORDER, ");
- Text_io.put_line ("FILE_ORDER ");
- SP.release;
- when internal_error =>
- Text_io.put ("Compile_Order internal error");
- when others =>
- Text_io.put ("Compile_Order internal error");
-
- end compile_order;
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --REPORT.SPC
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- package report_pkg is
- --| Package containing the reporting routines for compile_order.
-
- --| Overview:
-
- --| The three routine are to report the dependencies, compilation lists,
- --| and cycles. Dependencies and compilation lists both have full and raw
- --| forms, in addition compilation list has options to just give one of the
- --| lists in raw form. Reporting cycles is always done in full form since
- --| anything following is incomplete and this has to be said up front.
- --| Dependency does both with and withed-by dependencies. The two
- --| compilation lists are: units_list and files_list.
-
- --- Type declarations ---
-
- type form_type is (full, raw, units, files);
-
- --- Operations Global to report_pkg ---
-
- procedure dependency_report(--| Using the information in the DAG
- --| form and output the dependency table
- report: in form_type --| output the report in full or raw form
- );
- --| Effects: Produces the dependency table. If the form type is raw no
- --| headers are written. if it is full all the dependencies and headers
- --| are written.
-
- --| N/A: Errors, Requires, Modifies
-
- ----------------
-
-
- procedure compilation_list( --| Using the DAG form and produce
- --| the compilation order list
- report: in form_type --| output the report in full or raw form
- );
- --| Raises:
-
- --| Effects: produces the compilation order list. It is in full or raw
- --| form depending on report.
-
- --| N/A: Errors, Requires, Modifies
-
- ----------------
-
- procedure report_cycles; --| Report any cycles found in the units given
-
-
- --| Effects: If there are any entries in the cycles dag it prints them out
- --| as the dependencies which cause cycles in the compilation order. This
- --| is done before any of the other reports.
-
- --| N/A: Errors, Requires, Modifies
-
- ----------------
- end report_pkg;
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --LOOKUP.SPC
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- with Lists;
- with string_pkg;
- with text_io;
-
- package lookup_lists is
-
- ---- Package Renames:
- package SP renames string_pkg;
-
- ---- Types
-
- type lookup_record is
- record
- unit_name : SP.string_type;
- file_name : SP.string_type;
- end record;
-
- package l_list_pkg is new lists(lookup_record);
- subtype l_list is l_list_pkg.list;
-
- ---- Exceptions
-
- wrong_format : exception; -- raised when there are not two words on
- -- a line
- not_found : exception; -- raised when a unit is not found in a
- -- list
-
- ---- Variables
-
- lookup_list : l_list := l_list_pkg.create;
-
- ---- Operations global to lookup lists
-
- procedure init_list ( --| initialize the list
- --| from the list in the file
- file : TEXT_IO.file_type
- );
- --| Raises: wrong_format
-
- function lookup ( --| lookup the file name for
- --| the given unit name.
- unit : in SP.string_type
- ) return SP.string_type;
- --| Raises: not_found
-
- end lookup_lists;
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --COMPORD.BDY
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- with Parser;
- with ParserDeclarations;
- with Host_Dependencies;
- with nodes;
- with units_dag_pkg;
- with TEXT_IO;
- with report_pkg; use report_pkg;
- with lookup_lists;
- with Paginated_Output;
-
- package body Comp_Order is
-
- --| Overview
- --| Expand any '*' notation in the list of files given as input.
- --| Then scan each input file for withs clauses. Build a DAG of
- --| units with an edge representing a with. Also add edges
- --| for the implicit with of a spec by a body. Add the unit
- --| name into the table of unit names.
- --|
- --| If the dependency report is to be printed, call dependency_report
- --| in comp_utils with the apropriate argument (full, or raw).
- --|
- --| If the compilation report is to be printed, call compilation_list
- --| in comp_utils with the apropriate argument (full, raw, units or
- --| files).
-
- --| clean up.
-
-
- use string_pkg; -- need use for "&"
-
- ------ Package renames
-
- package PG renames Paginated_Output;
- package PD renames ParserDeclarations;
- package HD renames Host_Dependencies;
- package WDAG renames units_dag_pkg;
-
- -- Types --
-
- token : PD.ParseStackElement;
-
- -- Local subprogram specifications --
-
- procedure do_inline_dependencies; --| add dependencies to bodies of units
- --| with inlines.
-
- --| Effects: For all of the units found to have inlines look at the
- --| predecessors of the spec and put in dependencies from these
- --| predecessors to the body. If any cycles are created ignore them
- --| as the compiler would too.
-
- --| Modifies: COD.withs_dag
-
- ----------------
-
- procedure check_file_dependencies ( --| procedure which checks whether
- --| the order of the units within the
- --| the file would cause a compilaiton
- --| problem.
- unit_list : --| list of the units in the file
- in out COD.id_list_pkg.list
- );
-
- --| Effects: This checks that there are no problems for compilation
- --| in the order units appear in the file. The unit_list is a list of
- --| unit name in the order in which they appear in the file. Obviously
- --| if a unit at the end of the file is withed by one in the beginning
- --| they cannot be compiled in this order. This will flag these cases.
- --| It checks their dependencies in the COD.withs_dag. The unit list is
- --| emptied in this process ready for the next file.
-
- --| Modifies: unit_list
-
- ------------------
-
-
- -- Operations global to comp_ord --
-
-
- procedure Compilation_Order ( --| Produces a report showing dependencies
- --| and a compilation order for the files input
- Source_List: in --| list of filenames for input
- COD.id_list_pkg.list;
- Output : SP.string_type --| Output file name
- := SP.create ("");
- Units_file : SP.string_type --| File containing pairs of file name,
- := SP.create(""); --| unit name for adding to report.
- Which_Report: in --| Indicates whether to write both
- report_type:= full --| tables or just one of them
- ) is
- --| Raises: FILE_NOT_FOUND
-
- --| Algorithm:
- --| Using filemgr.expand expand any '*' notation in the file_list
- --| Use the routine gather to read the files for any withs and
- --| store the information in a DAG.
- --| Use dep_report to output the dependencies part of the report
- --| Use comp_list to output the compilation order list at the end
- --| of the report.
-
- ------ local declarations -----
-
- index : POSITIVE;
- iter : COD.id_list_pkg.ListIter;
- file : string_pkg.string_type;
- line : Host_Dependencies.Source_line;
- input_source : TEXT_IO.FILE_TYPE;
- output_file : TEXT_IO.FILE_TYPE;
- list_file : TEXT_IO.FILE_TYPE;
-
-
- begin
- -- the file list should be expanded before this program is called.
- -- This is done by UTS on the IBM and the command line interface
- -- package on VMS. If and when the preamble generator is working
- -- a filemanager expand may be needed, but it can't be done that
- -- way for now --cag
-
- if (Which_Report = full) or
- (Which_Report = dependency) or
- (Which_Report = compilation) then
- PG.Create_Paginated_File (File_Name => SP.value (Output),
- File_Handle => COD.report_file,
- Page_Size => 60,
- Header_size => 4,
- Footer_Size => 0);
- PG.Set_Header (File_Handle => COD.report_file,
- Header_Line => 1,
- Header_Text =>
- "Compilation Report ~c page ~p"
- );
- else
- -- the report type is raw so we don't want any headers or footers
- PG.Create_Paginated_File (File_Name => SP.value (Output),
- File_Handle => COD.report_file,
- Page_Size => 0,
- Header_size => 0,
- Footer_Size => 0);
- end if;
-
- if not SP.equal (Units_file, "") then
- begin
- text_io.open (file => list_file,
- mode => text_io.in_file,
- name => SP.value (Units_file));
- lookup_lists.init_list (list_file);
- text_io.close (list_file);
- exception
- when others =>
- Text_io.put_line ("Error opening the Units_File: " &
- SP.value (Units_File));
- Text_io.put_line ("Input from Units_File ignored");
- end;
- end if;
-
- iter := COD.id_list_pkg.MakeListIter (Source_List);
- while COD.id_list_pkg.more (iter) loop
- begin
-
- COD.id_list_pkg.next (iter, file);
- TEXT_IO.OPEN (
- FILE => input_source,
- MODE => TEXT_IO.IN_FILE,
- NAME => SP.value (file));
- TEXT_IO.SET_INPUT (input_source);
-
- COD.current_file := file;
- SP.mark;
- token := Parser.Parse;
- SP.release;
- check_file_dependencies (COD.unit_list);
- exception
- when PD.Parser_Error =>
- TEXT_IO.NEW_LINE;
- TEXT_IO.PUT_LINE(ITEM => "Syntax Error in Source: Line: " &
- HD.Source_Line'Image(PD.CurToken.lexed_token.srcpos_line) &
- " Column: " & HD.Source_Column'Image(
- PD.CurToken.lexed_token.srcpos_column));
- TEXT_IO.put ("In file: ");
- TEXT_IO.put_line (SP.value (COD.current_file));
- TEXT_IO.put_line ("Continuing with next file");
- when COD.duplicate_name =>
- Text_IO.put ("Two library units both have the name ");
- Text_IO.put (SP.value (COD.dup_string));
- TEXT_IO.put (", one of them in the file: ");
- TEXT_IO.put_line (SP.value (COD.current_file));
- TEXT_IO.put ("The other in ");
- TEXT_IO.put_line (SP.value (COD.dup_file));
- TEXT_IO.put_line ("Continuing with next file");
- when text_io.status_error =>
- Text_io.put
- ("Input file " & SP.value (file));
- Text_io.put_line
- (" is already open ");
- Text_io.put_line ("Continuing with next file");
- when Text_io.name_error =>
- Text_io.put_line
- ("Unknown input_file: " & SP.value (file));
- Text_io.put_line ("Continuing with next file");
- when Text_io.use_error =>
- Text_io.put_line
- ("Error opening input file: " & SP.value (file));
- Text_io.put_line ("Continuing with next file");
- end;
- begin
- TEXT_IO.CLOSE (input_source);
- exception
- when Text_io.status_error =>
- -- raised when the input file couldn't be opened which has already
- -- been reported so ignore this.
- null;
- end;
- end loop;
-
- do_inline_dependencies;
-
- case Which_Report is
- when full =>
- report_cycles;
- dependency_report (full);
- compilation_list (full);
- when raw =>
- report_cycles;
- dependency_report (raw);
- compilation_list (raw);
- when dependency =>
- report_cycles;
- dependency_report (full);
- when raw_dependency =>
- report_cycles;
- dependency_report (raw);
- when compilation =>
- report_cycles;
- compilation_list (full);
- when raw_compilation =>
- report_cycles;
- compilation_list (raw);
- when units_order =>
- report_cycles;
- compilation_list (units);
- when file_order =>
- report_cycles;
- compilation_list (files);
- end case;
-
- PG.Close_Paginated_File (File_Handle => COD.report_file);
-
- exception
- when PG.file_error =>
- Text_io.put_line
- ("Error opening report file : report not generated");
- when PG.file_already_open =>
- Text_io.put_line
- ("Report file already open : report not generated");
- when others =>
- raise internal_error;
-
- end Compilation_Order;
-
-
- ----------------
-
- procedure do_inline_dependencies --| add dependencies to bodies of units
- --| with inlines.
- is
-
- i : COD.id_set_pkg.members_iter;
- name : SP.string_type;
- body_name : SP.string_type;
- body_label : SP.string_type;
- body_temp : SP.string_type;
- spec_label : SP.string_type;
- predecessor : SP.string_type;
- preds : WDAG.preds_iter;
- value : nodes.dag_node;
-
- begin
- SP.mark;
-
- i := COD.id_set_pkg.make_members_iter(COD.inline_set);
- while COD.id_set_pkg.more (i) loop
- COD.id_set_pkg.next (i, name);
- body_name := name & " (body)";
- body_temp := SP.make_persistent (SP.upper (body_name));
- body_label := SP.upper (body_name);
- spec_label := SP.upper (name & " (spec)");
-
- begin
- value := COD.default_node;
- value.name := SP.make_persistent (body_name);
- WDAG.add_node (COD.withs_dag,
- body_temp,
- value);
- WDAG.add_edge (COD.withs_dag, body_label, spec_label);
- exception
- when WDAG.illegal_node | WDAG.duplicate_edge=>
- SP.flush (body_temp);
- SP.flush (value.name);
- end;
- preds := WDAG.make_preds_iter (COD.withs_dag, spec_label);
- while WDAG.more (preds) loop
- WDAG.next (preds, predecessor);
- begin
- WDAG.add_edge (COD.withs_dag, predecessor, body_label);
- exception
- when WDAG.makes_cycle | WDAG.duplicate_edge =>
- -- one of the specs predecessors is the body so this
- -- will always happen just ignore it.
- -- And there shouldn't be duplicate edges, but if
- -- there are ignore them.
- null;
- end;
- end loop;
- end loop;
- SP.release;
-
- end do_inline_dependencies;
-
- ----------------
-
- procedure check_file_dependencies ( --| procedure which checks whether
- --| the order of the units within the
- --| the file would cause a compilaiton
- --| problem.
- unit_list : in out COD.id_list_pkg.list
- --| list of the units in the file
- ) is
-
- id_iter : COD.id_list_pkg.ListIter;
- top : SP.string_type;
- element : SP.string_type;
- elt : SP.string_type;
- top_value : nodes.dag_node;
- elt_value : nodes.dag_node;
- begin
- SP.mark;
-
- while not COD.id_list_pkg.IsEmpty (unit_list) loop
- top := SP.upper (COD.id_list_pkg.FirstValue (unit_list));
- COD.id_list_pkg.DeleteHead (unit_list);
- id_iter := COD.id_list_pkg.MakeListIter (unit_list);
- while COD.id_list_pkg.More (id_iter) loop
- COD.id_list_pkg.Next (id_iter, element);
- elt := SP.upper (element);
- if WDAG.is_descendent (COD.withs_dag, top, elt) then
- begin
- top_value := WDAG.get_value (COD.withs_dag, top);
- elt_value := WDAG.get_value (COD.withs_dag, elt);
- top_value.trouble_node := true;
- elt_value.trouble_node := true;
- WDAG.set_value (COD.withs_dag, top, top_value);
- WDAG.set_value (COD.withs_dag, elt, elt_value);
- exception
- when WDAG.illegal_node =>
- -- something's already wrong if one is in cycle dag
- -- instead of withs so ignore it.
- null;
- end;
- end if;
- end loop;
- end loop;
- SP.release;
- end check_file_dependencies;
-
- end Comp_Order;
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --GRMCONST.BDY
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
-
- Package body Grammar_Constants is
-
- function setGrammarSymbolCount return ParserInteger is
- begin
- return 319 ;
- end setGrammarSymbolCount;
-
- function setActionCount return ParserInteger is
- begin
- return 1429 ;
- end setActionCount;
-
- function setStateCountPlusOne return ParserInteger is
- begin
- return 950 ;
- end setStateCountPlusOne;
-
- function setLeftHandSideCount return ParserInteger is
- begin
- return 477 ;
- end setLeftHandSideCount;
-
- function setRightHandSideCount return ParserInteger is
- begin
- return 477 ;
- end setRightHandSideCount;
-
- end Grammar_Constants;
-
-
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --PTBLS.BDY
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
-
- package body ParseTables is
- ----------------------------------------------------------------------
- -- The rest of the constants used to the Parse Tables
- ----------------------------------------------------------------------
-
- DefaultValue : constant := 1 ; -- default for aggregates.
-
- ActionTableOneLength : constant GC.ParserInteger :=
- 8225 ;
- --| Length (number of entries) in map ActionTableOne.
- subtype ActionTableOneRange is GC.ParserInteger
- range 1..ActionTableOneLength;
-
- ActionTableTwoLength : constant GC.ParserInteger :=
- 8225 ;
- --| Length (number of entries) in map ActionTableTwo.
- subtype ActionTableTwoRange is GC.ParserInteger
- range 1..ActionTableTwoLength;
-
- DefaultMapLength : constant GC.ParserInteger :=
- 949 ;
- --| Length (number of entries) in map Defaults.
- subtype DefaultMapRange is GC.ParserInteger range 1..DefaultMapLength;
-
- FollowMapLength : constant GC.ParserInteger :=
- 223 ;
- --| Length (number of entries) in the FollowMap.
-
- GrammarSymbolCountPlusOne : constant GC.ParserInteger :=
- 320 ;
- --| Number of symbols plus one in the parse tables.
- -- NYU Reference Name: NUM_INPUTS
-
- ActionTableSize : constant GC.ParserInteger :=
- 5519 ;
- --| Maximum entry in Action Tables referenced by hash
- --| function. Entries above TableSize are collision chains.
- -- NYU Reference Name: TABLE_SIZE
-
- ------------------------------------------------------------------
- -- Tables generated by Parse Tables Generator
- ------------------------------------------------------------------
-
- subtype GrammarSymbolRepRangePlusZero is
- GrammarSymbolRepRangePlusZeroCommon;
-
- GrammarSymbolTableIndex : constant
- array (GrammarSymbolRange'first .. GrammarSymbolRange'last * 2)
- of GC.ParserInteger :=
- ( 1, 0, 1, 5, 6, 8, 9, 14, 15, 20
- , 21, 23, 24, 26, 27, 31, 32, 33, 34, 38
- , 39, 42, 43, 46, 47, 54, 55, 61, 62, 66
- , 67, 71, 72, 77, 78, 79, 80, 83, 84, 88
- , 89, 91, 92, 96, 97, 105, 106, 109, 110, 112
- , 113, 120, 121, 127, 128, 131, 132, 133, 134, 135
- , 136, 137, 138, 144, 145, 148, 149, 151, 152, 154
- , 155, 157, 158, 161, 162, 163, 164, 165, 166, 171
- , 172, 174, 175, 181, 182, 187, 188, 194, 195, 203
- , 204, 208, 209, 213, 214, 219, 220, 222, 223, 229
- , 230, 235, 236, 242, 243, 248, 249, 256, 257, 263
- , 264, 267, 268, 276, 277, 280, 281, 284, 285, 287
- , 288, 291, 292, 296, 297, 300, 301, 303, 304, 313
- , 314, 328, 329, 342, 343, 359, 360, 360, 361, 361
- , 362, 362, 363, 363, 364, 364, 365, 365, 366, 366
- , 367, 367, 368, 368, 369, 369, 370, 370, 371, 371
- , 372, 372, 373, 373, 374, 374, 375, 377, 378, 379
- , 380, 381, 382, 383, 384, 385, 386, 387, 388, 389
- , 390, 391, 392, 393, 394, 395, 396, 397, 398, 412
- , 413, 416, 417, 420, 421, 431, 432, 440, 441, 470
- , 471, 476, 477, 494, 495, 511, 512, 529, 530, 545
- , 546, 564, 565, 586, 587, 605, 606, 621, 622, 640
- , 641, 661, 662, 682, 683, 702, 703, 717, 718, 735
- , 736, 749, 750, 777, 778, 787, 788, 800, 801, 821
- , 822, 848, 849, 872, 873, 887, 888, 913, 914, 942
- , 943, 969, 970, 992, 993, 1012, 1013, 1033, 1034, 1055
- , 1056, 1077, 1078, 1100, 1101, 1109, 1110, 1119, 1120, 1141
- , 1142, 1157, 1158, 1182, 1183, 1204, 1205, 1221, 1222, 1254
- , 1255, 1290, 1291, 1309, 1310, 1337, 1338, 1355, 1356, 1380
- , 1381, 1410, 1411, 1434, 1435, 1461, 1462, 1477, 1478, 1481
- , 1482, 1495, 1496, 1512, 1513, 1517, 1518, 1531, 1532, 1544
- , 1545, 1567, 1568, 1588, 1589, 1600, 1601, 1616, 1617, 1623
- , 1624, 1632, 1633, 1638, 1639, 1647, 1648, 1671, 1672, 1687
- , 1688, 1691, 1692, 1715, 1716, 1737, 1738, 1758, 1759, 1768
- , 1769, 1790, 1791, 1801, 1802, 1810, 1811, 1825, 1826, 1837
- , 1838, 1846, 1847, 1863, 1864, 1881, 1882, 1890, 1891, 1898
- , 1899, 1918, 1919, 1940, 1941, 1949, 1950, 1983, 1984, 2004
- , 2005, 2031, 2032, 2061, 2062, 2079, 2080, 2108, 2109, 2143
- , 2144, 2181, 2182, 2189, 2190, 2212, 2213, 2234, 2235, 2257
- , 2258, 2286, 2287, 2314, 2315, 2354, 2355, 2361, 2362, 2418
- , 2419, 2454, 2455, 2458, 2459, 2465, 2466, 2499, 2500, 2505
- , 2506, 2535, 2536, 2559, 2560, 2568, 2569, 2588, 2589, 2607
- , 2608, 2629, 2630, 2650, 2651, 2670, 2671, 2693, 2694, 2706
- , 2707, 2718, 2719, 2727, 2728, 2738, 2739, 2760, 2761, 2776
- , 2777, 2794, 2795, 2802, 2803, 2816, 2817, 2836, 2837, 2850
- , 2851, 2866, 2867, 2880, 2881, 2895, 2896, 2910, 2911, 2925
- , 2926, 2939, 2940, 2953, 2954, 2965, 2966, 2979, 2980, 2993
- , 2994, 3008, 3009, 3024, 3025, 3040, 3041, 3045, 3046, 3083
- , 3084, 3131, 3132, 3161, 3162, 3170, 3171, 3182, 3183, 3208
- , 3209, 3236, 3237, 3254, 3255, 3266, 3267, 3280, 3281, 3295
- , 3296, 3328, 3329, 3364, 3365, 3383, 3384, 3407, 3408, 3422
- , 3423, 3445, 3446, 3471, 3472, 3481, 3482, 3485, 3486, 3507
- , 3508, 3523, 3524, 3544, 3545, 3568, 3569, 3598, 3599, 3614
- , 3615, 3632, 3633, 3651, 3652, 3674, 3675, 3705, 3706, 3722
- , 3723, 3749, 3750, 3763, 3764, 3785, 3786, 3801, 3802, 3819
- , 3820, 3843, 3844, 3869, 3870, 3887, 3888, 3904, 3905, 3925
- , 3926, 3949, 3950, 3956, 3957, 3974, 3975, 3987, 3988, 4003
- , 4004, 4017, 4018, 4042, 4043, 4049, 4050, 4074, 4075, 4081
- , 4082, 4096, 4097, 4107, 4108, 4116, 4117, 4132, 4133, 4151
- , 4152, 4168, 4169, 4189, 4190, 4208, 4209, 4239, 4240, 4268
- , 4269, 4291, 4292, 4309, 4310, 4321, 4322, 4340, 4341, 4362
- , 4363, 4414, 4415, 4438, 4439, 4462, 4463, 4475, 4476, 4508
- , 4509, 4522, 4523, 4550, 4551, 4568, 4569, 4584, 4585, 4600
- , 4601, 4613, 4614, 4626, 4627, 4648, 4649, 4663) ;
-
- GrammarSymbolTable : constant String :=
- ('A','B','O','R','T','A','B','S','A','C'
- ,'C','E','P','T','A','C','C','E','S','S'
- ,'A','L','L','A','N','D','A','R','R','A'
- ,'Y','A','T','B','E','G','I','N','B','O'
- ,'D','Y','C','A','S','E','C','O','N','S'
- ,'T','A','N','T','D','E','C','L','A','R'
- ,'E','D','E','L','A','Y','D','E','L','T'
- ,'A','D','I','G','I','T','S','D','O','E'
- ,'L','S','E','E','L','S','I','F','E','N'
- ,'D','E','N','T','R','Y','E','X','C','E'
- ,'P','T','I','O','N','E','X','I','T','F'
- ,'O','R','F','U','N','C','T','I','O','N'
- ,'G','E','N','E','R','I','C','G','O','T'
- ,'O','I','F','I','N','I','S','L','I','M'
- ,'I','T','E','D','L','O','O','P','M','O'
- ,'D','N','E','W','N','O','T','N','U','L'
- ,'L','O','F','O','R','O','T','H','E','R'
- ,'S','O','U','T','P','A','C','K','A','G'
- ,'E','P','R','A','G','M','A','P','R','I'
- ,'V','A','T','E','P','R','O','C','E','D'
- ,'U','R','E','R','A','I','S','E','R','A'
- ,'N','G','E','R','E','C','O','R','D','R'
- ,'E','M','R','E','N','A','M','E','S','R'
- ,'E','T','U','R','N','R','E','V','E','R'
- ,'S','E','S','E','L','E','C','T','S','E'
- ,'P','A','R','A','T','E','S','U','B','T'
- ,'Y','P','E','T','A','S','K','T','E','R'
- ,'M','I','N','A','T','E','T','H','E','N'
- ,'T','Y','P','E','U','S','E','W','H','E'
- ,'N','W','H','I','L','E','W','I','T','H'
- ,'X','O','R','i','d','e','n','t','i','f'
- ,'i','e','r','n','u','m','e','r','i','c'
- ,'_','l','i','t','e','r','a','l','s','t'
- ,'r','i','n','g','_','l','i','t','e','r'
- ,'a','l','c','h','a','r','a','c','t','e'
- ,'r','_','l','i','t','e','r','a','l','&'
- ,''','(',')','*','+',',','-','.','/',':'
- ,';','<','=','>',''','|',''','=','>','.'
- ,'.','*','*',':','=','/','=','>','=','<'
- ,'=','<','<','>','>','<','>','c','o','m'
- ,'m','e','n','t','_','l','i','t','e','r'
- ,'a','l','$','E','O','F','$','A','C','C'
- ,'c','o','m','p','i','l','a','t','i','o'
- ,'n','p','r','a','g','m','a','_','i','d'
- ,'g','e','n','e','r','a','l','_','c','o'
- ,'m','p','o','n','e','n','t','_','a','s'
- ,'s','o','c','i','a','t','i','o','n','s'
- ,'p','r','a','g','m','a','o','b','j','e'
- ,'c','t','_','d','e','c','l','a','r','a'
- ,'t','i','o','n','b','a','s','i','c','_'
- ,'d','e','c','l','a','r','a','t','i','o'
- ,'n','n','u','m','b','e','r','_','d','e'
- ,'c','l','a','r','a','t','i','o','n','t'
- ,'y','p','e','_','d','e','c','l','a','r'
- ,'a','t','i','o','n','s','u','b','t','y'
- ,'p','e','_','d','e','c','l','a','r','a'
- ,'t','i','o','n','s','u','b','p','r','o'
- ,'g','r','a','m','_','d','e','c','l','a'
- ,'r','a','t','i','o','n','p','a','c','k'
- ,'a','g','e','_','d','e','c','l','a','r'
- ,'a','t','i','o','n','t','a','s','k','_'
- ,'d','e','c','l','a','r','a','t','i','o'
- ,'n','g','e','n','e','r','i','c','_','d'
- ,'e','c','l','a','r','a','t','i','o','n'
- ,'e','x','c','e','p','t','i','o','n','_'
- ,'d','e','c','l','a','r','a','t','i','o'
- ,'n','g','e','n','e','r','i','c','_','i'
- ,'n','s','t','a','n','t','i','a','t','i'
- ,'o','n','r','e','n','a','m','i','n','g'
- ,'_','d','e','c','l','a','r','a','t','i'
- ,'o','n','i','d','e','n','t','i','f','i'
- ,'e','r','_','l','i','s','t','s','u','b'
- ,'t','y','p','e','_','i','n','d','i','c'
- ,'a','t','i','o','n','[',':','=','e','x'
- ,'p','r','e','s','s','i','o','n',']','c'
- ,'o','n','s','t','r','a','i','n','e','d'
- ,'_','a','r','r','a','y','_','d','e','f'
- ,'i','n','i','t','i','o','n','e','x','p'
- ,'r','e','s','s','i','o','n','{',',','i'
- ,'d','e','n','t','i','f','i','e','r','}'
- ,'f','u','l','l','_','t','y','p','e','_'
- ,'d','e','c','l','a','r','a','t','i','o'
- ,'n','i','n','c','o','m','p','l','e','t'
- ,'e','_','t','y','p','e','_','d','e','c'
- ,'l','a','r','a','t','i','o','n','p','r'
- ,'i','v','a','t','e','_','t','y','p','e'
- ,'_','d','e','c','l','a','r','a','t','i'
- ,'o','n','t','y','p','e','_','d','e','f'
- ,'i','n','i','t','i','o','n','d','i','s'
- ,'c','r','i','m','i','n','a','n','t','_'
- ,'s','p','e','c','i','f','i','c','a','t'
- ,'i','o','n','{',';','d','i','s','c','r'
- ,'i','m','i','n','a','n','t','_','s','p'
- ,'e','c','i','f','i','c','a','t','i','o'
- ,'n','}','e','n','u','m','e','r','a','t'
- ,'i','o','n','_','t','y','p','e','_','d'
- ,'e','f','i','n','i','t','i','o','n','i'
- ,'n','t','e','g','e','r','_','t','y','p'
- ,'e','_','d','e','f','i','n','i','t','i'
- ,'o','n','r','e','a','l','_','t','y','p'
- ,'e','_','d','e','f','i','n','i','t','i'
- ,'o','n','a','r','r','a','y','_','t','y'
- ,'p','e','_','d','e','f','i','n','i','t'
- ,'i','o','n','r','e','c','o','r','d','_'
- ,'t','y','p','e','_','d','e','f','i','n'
- ,'i','t','i','o','n','a','c','c','e','s'
- ,'s','_','t','y','p','e','_','d','e','f'
- ,'i','n','i','t','i','o','n','d','e','r'
- ,'i','v','e','d','_','t','y','p','e','_'
- ,'d','e','f','i','n','i','t','i','o','n'
- ,'t','y','p','e','_','m','a','r','k','c'
- ,'o','n','s','t','r','a','i','n','t','t'
- ,'y','p','e','_','n','a','m','e','|','s'
- ,'u','b','t','y','p','e','_','n','a','m'
- ,'e','r','a','n','g','e','_','c','o','n'
- ,'s','t','r','a','i','n','t','f','l','o'
- ,'a','t','i','n','g','_','p','o','i','n'
- ,'t','_','c','o','n','s','t','r','a','i'
- ,'n','t','f','i','x','e','d','_','p','o'
- ,'i','n','t','_','c','o','n','s','t','r'
- ,'a','i','n','t','s','i','m','p','l','e'
- ,'_','e','x','p','r','e','s','s','i','o'
- ,'n','e','n','u','m','e','r','a','t','i'
- ,'o','n','_','l','i','t','e','r','a','l'
- ,'_','s','p','e','c','i','f','i','c','a'
- ,'t','i','o','n','{',',','e','n','u','m'
- ,'e','r','a','t','i','o','n','_','l','i'
- ,'t','e','r','a','l','_','s','p','e','c'
- ,'i','f','i','c','a','t','i','o','n','}'
- ,'e','n','u','m','e','r','a','t','i','o'
- ,'n','_','l','i','t','e','r','a','l','f'
- ,'l','o','a','t','i','n','g','_','a','c'
- ,'c','u','r','a','c','y','_','d','e','f'
- ,'i','n','i','t','i','o','n','[','r','a'
- ,'n','g','e','_','c','o','n','s','t','r'
- ,'a','i','n','t',']','f','i','x','e','d'
- ,'_','a','c','c','u','r','a','c','y','_'
- ,'d','e','f','i','n','i','t','i','o','n'
- ,'u','n','c','o','n','s','t','r','a','i'
- ,'n','e','d','_','a','r','r','a','y','_'
- ,'d','e','f','i','n','i','t','i','o','n'
- ,'i','n','d','e','x','_','s','u','b','t'
- ,'y','p','e','_','d','e','f','i','n','i'
- ,'t','i','o','n','{',',','i','n','d','e'
- ,'x','_','s','u','b','t','y','p','e','_'
- ,'d','e','f','i','n','i','t','i','o','n'
- ,'}','i','n','d','e','x','_','c','o','n'
- ,'s','t','r','a','i','n','t','n','a','m'
- ,'e','d','i','s','c','r','e','t','e','_'
- ,'r','a','n','g','e','{',',','d','i','s'
- ,'c','r','e','t','e','_','r','a','n','g'
- ,'e','}','r','a','n','g','e','c','o','m'
- ,'p','o','n','e','n','t','_','l','i','s'
- ,'t','{','p','r','a','g','m','a','_','d'
- ,'e','c','l','}','{','c','o','m','p','o'
- ,'n','e','n','t','_','d','e','c','l','a'
- ,'r','a','t','i','o','n','}','c','o','m'
- ,'p','o','n','e','n','t','_','d','e','c'
- ,'l','a','r','a','t','i','o','n','v','a'
- ,'r','i','a','n','t','_','p','a','r','t'
- ,'{','p','r','a','g','m','a','_','v','a'
- ,'r','i','a','n','t','}','v','a','r','i'
- ,'a','n','t','{','v','a','r','i','a','n'
- ,'t','}','c','h','o','i','c','e','{','|'
- ,'c','h','o','i','c','e','}','{','b','a'
- ,'s','i','c','_','d','e','c','l','a','r'
- ,'a','t','i','v','e','_','i','t','e','m'
- ,'}','d','e','c','l','a','r','a','t','i'
- ,'v','e','_','p','a','r','t','b','o','d'
- ,'y','{','l','a','t','e','r','_','d','e'
- ,'c','l','a','r','a','t','i','v','e','_'
- ,'i','t','e','m','}','b','a','s','i','c'
- ,'_','d','e','c','l','a','r','a','t','i'
- ,'v','e','_','i','t','e','m','r','e','p'
- ,'r','e','s','e','n','t','a','t','i','o'
- ,'n','_','c','l','a','u','s','e','u','s'
- ,'e','_','c','l','a','u','s','e','l','a'
- ,'t','e','r','_','d','e','c','l','a','r'
- ,'a','t','i','v','e','_','i','t','e','m'
- ,'p','r','o','p','e','r','_','b','o','d'
- ,'y','b','o','d','y','_','s','t','u','b'
- ,'s','u','b','p','r','o','g','r','a','m'
- ,'_','b','o','d','y','p','a','c','k','a'
- ,'g','e','_','b','o','d','y','t','a','s'
- ,'k','_','b','o','d','y','i','n','d','e'
- ,'x','e','d','_','c','o','m','p','o','n'
- ,'e','n','t','s','e','l','e','c','t','e'
- ,'d','_','c','o','m','p','o','n','e','n'
- ,'t','a','t','t','r','i','b','u','t','e'
- ,'s','e','l','e','c','t','o','r','a','t'
- ,'t','r','i','b','u','t','e','_','d','e'
- ,'s','i','g','n','a','t','o','r','c','o'
- ,'m','p','o','n','e','n','t','_','a','s'
- ,'s','o','c','i','a','t','i','o','n','s'
- ,'a','g','g','r','e','g','a','t','e','e'
- ,'x','p','r','e','s','s','i','o','n',','
- ,'e','x','p','r','e','s','s','i','o','n'
- ,'{',',','e','x','p','r','e','s','s','i'
- ,'o','n','}','[',',','o','t','h','e','r'
- ,'s','=','>','e','x','p','r','e','s','s'
- ,'i','o','n',']','c','h','o','i','c','e'
- ,'{','|','c','h','o','i','c','e','}','='
- ,'>','e','x','p','r','e','s','s','i','o'
- ,'n','{',',','c','h','o','i','c','e','{'
- ,'|','c','h','o','i','c','e','}','=','>'
- ,'e','x','p','r','e','s','s','i','o','n'
- ,'}','o','t','h','e','r','s','=','>','e'
- ,'x','p','r','e','s','s','i','o','n','g'
- ,'a','_','e','x','p','r','e','s','s','i'
- ,'o','n','{',',','g','a','_','e','x','p'
- ,'r','e','s','s','i','o','n','}','i','d'
- ,'e','n','t','i','f','i','e','r','{','|'
- ,'i','d','e','n','t','i','f','i','e','r'
- ,'}','=','>','e','x','p','r','e','s','s'
- ,'i','o','n','{',',','i','d','e','n','t'
- ,'i','f','i','e','r','{','|','i','d','e'
- ,'n','t','i','f','i','e','r','}','=','>'
- ,'e','x','p','r','e','s','s','i','o','n'
- ,'}','r','e','l','a','t','i','o','n','r'
- ,'e','l','a','t','i','o','n','{','A','N'
- ,'D','_','_','r','e','l','a','t','i','o'
- ,'n','}','r','e','l','a','t','i','o','n'
- ,'{','O','R','_','_','r','e','l','a','t'
- ,'i','o','n','}','r','e','l','a','t','i'
- ,'o','n','{','X','O','R','_','_','r','e'
- ,'l','a','t','i','o','n','}','r','e','l'
- ,'a','t','i','o','n','{','A','N','D','_'
- ,'_','T','H','E','N','_','_','r','e','l'
- ,'a','t','i','o','n','}','r','e','l','a'
- ,'t','i','o','n','{','O','R','_','_','E'
- ,'L','S','E','_','_','r','e','l','a','t'
- ,'i','o','n','}','[','r','e','l','a','t'
- ,'i','o','n','a','l','_','o','p','e','r'
- ,'a','t','o','r','_','_','s','i','m','p'
- ,'l','e','_','e','x','p','r','e','s','s'
- ,'i','o','n',']','[','N','O','T',']','I'
- ,'N','[','u','n','a','r','y','_','a','d'
- ,'d','i','n','g','_','o','p','e','r','a'
- ,'t','o','r',']','t','e','r','m','{','b'
- ,'i','n','a','r','y','_','a','d','d','i'
- ,'n','g','_','o','p','e','r','a','t','o'
- ,'r','_','_','t','e','r','m','}','f','a'
- ,'c','t','o','r','{','m','u','l','t','i'
- ,'p','l','y','i','n','g','_','o','p','e'
- ,'r','a','t','o','r','_','_','f','a','c'
- ,'t','o','r','}','t','e','r','m','p','r'
- ,'i','m','a','r','y','[','e','x','p','o'
- ,'n','e','n','t','i','a','t','i','n','g'
- ,'_','o','p','e','r','a','t','o','r','_'
- ,'_','p','r','i','m','a','r','y',']','f'
- ,'a','c','t','o','r','h','i','g','h','_'
- ,'p','r','e','c','e','d','e','n','c','e'
- ,'_','u','n','a','r','y','_','o','p','e'
- ,'r','a','t','o','r','p','a','r','e','n'
- ,'t','h','e','s','i','z','e','d','_','e'
- ,'x','p','r','e','s','s','i','o','n','a'
- ,'l','l','o','c','a','t','o','r','q','u'
- ,'a','l','i','f','i','e','d','_','e','x'
- ,'p','r','e','s','s','i','o','n','r','e'
- ,'l','a','t','i','o','n','a','l','_','o'
- ,'p','e','r','a','t','o','r','b','i','n'
- ,'a','r','y','_','a','d','d','i','n','g'
- ,'_','o','p','e','r','a','t','o','r','u'
- ,'n','a','r','y','_','a','d','d','i','n'
- ,'g','_','o','p','e','r','a','t','o','r'
- ,'m','u','l','t','i','p','l','y','i','n'
- ,'g','_','o','p','e','r','a','t','o','r'
- ,'e','x','p','o','n','e','n','t','i','a'
- ,'t','i','n','g','_','o','p','e','r','a'
- ,'t','o','r','e','x','p','a','n','d','e'
- ,'d','_','n','a','m','e','{','p','r','a'
- ,'g','m','a','_','s','t','m','}','s','t'
- ,'a','t','e','m','e','n','t','{','s','t'
- ,'a','t','e','m','e','n','t','}','s','e'
- ,'q','u','e','n','c','e','_','o','f','_'
- ,'s','t','a','t','e','m','e','n','t','s'
- ,'s','i','m','p','l','e','_','s','t','a'
- ,'t','e','m','e','n','t','c','o','m','p'
- ,'o','u','n','d','_','s','t','a','t','e'
- ,'m','e','n','t','{','l','a','b','e','l'
- ,'}','+','n','u','l','l','_','s','t','a'
- ,'t','e','m','e','n','t','a','s','s','i'
- ,'g','n','m','e','n','t','_','s','t','a'
- ,'t','e','m','e','n','t','e','x','i','t'
- ,'_','s','t','a','t','e','m','e','n','t'
- ,'r','e','t','u','r','n','_','s','t','a'
- ,'t','e','m','e','n','t','g','o','t','o'
- ,'_','s','t','a','t','e','m','e','n','t'
- ,'d','e','l','a','y','_','s','t','a','t'
- ,'e','m','e','n','t','a','b','o','r','t'
- ,'_','s','t','a','t','e','m','e','n','t'
- ,'r','a','i','s','e','_','s','t','a','t'
- ,'e','m','e','n','t','c','o','d','e','_'
- ,'s','t','a','t','e','m','e','n','t','c'
- ,'a','l','l','_','s','t','a','t','e','m'
- ,'e','n','t','i','f','_','s','t','a','t'
- ,'e','m','e','n','t','c','a','s','e','_'
- ,'s','t','a','t','e','m','e','n','t','l'
- ,'o','o','p','_','s','t','a','t','e','m'
- ,'e','n','t','b','l','o','c','k','_','s'
- ,'t','a','t','e','m','e','n','t','a','c'
- ,'c','e','p','t','_','s','t','a','t','e'
- ,'m','e','n','t','s','e','l','e','c','t'
- ,'_','s','t','a','t','e','m','e','n','t'
- ,'l','a','b','e','l','c','o','n','d','i'
- ,'t','i','o','n','_','T','H','E','N','_'
- ,'_','s','e','q','u','e','n','c','e','_'
- ,'o','f','_','s','t','a','t','e','m','e'
- ,'n','t','s','{','E','L','S','I','F','_'
- ,'_','c','o','n','d','i','t','i','o','n'
- ,'_','_','T','H','E','N','_','_','s','e'
- ,'q','u','e','n','c','e','_','o','f','_'
- ,'s','t','a','t','e','m','e','n','t','s'
- ,'}','[','E','L','S','E','_','_','s','e'
- ,'q','u','e','n','c','e','_','o','f','_'
- ,'s','t','a','t','e','m','e','n','t','s'
- ,']','c','o','n','d','i','t','i','o','n'
- ,'{','p','r','a','g','m','a','_','a','l'
- ,'t','}','c','a','s','e','_','s','t','a'
- ,'t','e','m','e','n','t','_','a','l','t'
- ,'e','r','n','a','t','i','v','e','{','c'
- ,'a','s','e','_','s','t','a','t','e','m'
- ,'e','n','t','_','a','l','t','e','r','n'
- ,'a','t','i','v','e','}','[','l','o','o'
- ,'p','_','i','d','e','n','t','i','f','i'
- ,'e','r',':',']','[','i','d','e','n','t'
- ,'i','f','i','e','r',']','i','t','e','r'
- ,'a','t','i','o','n','_','r','u','l','e'
- ,'b','e','g','i','n','_','e','n','d','_'
- ,'b','l','o','c','k','d','e','c','l','a'
- ,'r','a','t','i','v','e','_','p','a','r'
- ,'t','_','_','b','e','g','i','n','_','e'
- ,'n','d','_','b','l','o','c','k','{','p'
- ,'r','a','g','m','a','_','a','l','t','}'
- ,'_','_','e','x','c','e','p','t','i','o'
- ,'n','_','h','a','n','d','l','e','r','_'
- ,'l','i','s','t','[','b','l','o','c','k'
- ,'_','i','d','e','n','t','i','f','i','e'
- ,'r',':',']','s','u','b','p','r','o','g'
- ,'r','a','m','_','s','p','e','c','i','f'
- ,'i','c','a','t','i','o','n','u','n','i'
- ,'t','_','i','d','e','n','t','i','f','i'
- ,'e','r','p','a','r','a','m','e','t','e'
- ,'r','_','s','p','e','c','i','f','i','c'
- ,'a','t','i','o','n','{',';','p','a','r'
- ,'a','m','e','t','e','r','_','s','p','e'
- ,'c','i','f','i','c','a','t','i','o','n'
- ,'}','d','e','s','i','g','n','a','t','o'
- ,'r','m','o','d','e','g','e','n','e','r'
- ,'i','c','_','p','a','r','a','m','e','t'
- ,'e','r','_','m','o','d','e','[','e','n'
- ,'d','_','d','e','s','i','g','n','a','t'
- ,'o','r',']','p','a','c','k','a','g','e'
- ,'_','s','p','e','c','i','f','i','c','a'
- ,'t','i','o','n','p','a','c','k','a','g'
- ,'e','_','_','u','n','i','t','_','i','d'
- ,'e','n','t','i','f','i','e','r','p','a'
- ,'c','k','a','g','e','_','_','b','o','d'
- ,'y','_','_','u','n','i','t','_','i','d'
- ,'e','n','t','i','f','i','e','r','{',','
- ,'e','x','p','a','n','d','e','d','_','n'
- ,'a','m','e','}','t','a','s','k','_','s'
- ,'p','e','c','i','f','i','c','a','t','i'
- ,'o','n','{','e','n','t','r','y','_','d'
- ,'e','c','l','a','r','a','t','i','o','n'
- ,'}','{','r','e','p','r','e','s','e','n'
- ,'t','a','t','i','o','n','_','c','l','a'
- ,'u','s','e','}','[','(','d','i','s','c'
- ,'r','e','t','e','_','r','a','n','g','e'
- ,')',']','[','f','o','r','m','a','l','_'
- ,'p','a','r','t',']','e','n','t','r','y'
- ,'_','d','e','c','l','a','r','a','t','i'
- ,'o','n','[','(','e','x','p','r','e','s'
- ,'s','i','o','n',')',']','[','f','o','r'
- ,'m','a','l','_','p','a','r','t',']','s'
- ,'e','l','e','c','t','i','v','e','_','w'
- ,'a','i','t','c','o','n','d','i','t','i'
- ,'o','n','a','l','_','e','n','t','r','y'
- ,'_','c','a','l','l','t','i','m','e','d'
- ,'_','e','n','t','r','y','_','c','a','l'
- ,'l','s','e','l','e','c','t','_','a','l'
- ,'t','e','r','n','a','t','i','v','e','{'
- ,'O','R','_','_','s','e','l','e','c','t'
- ,'_','a','l','t','e','r','n','a','t','i'
- ,'v','e','}','s','e','l','e','c','t','i'
- ,'v','e','_','w','a','i','t','_','a','l'
- ,'t','e','r','n','a','t','i','v','e','a'
- ,'c','c','e','p','t','_','a','l','t','e'
- ,'r','n','a','t','i','v','e','d','e','l'
- ,'a','y','_','a','l','t','e','r','n','a'
- ,'t','i','v','e','t','e','r','m','i','n'
- ,'a','t','e','_','a','l','t','e','r','n'
- ,'a','t','i','v','e','[','s','e','q','u'
- ,'e','n','c','e','_','o','f','_','s','t'
- ,'a','t','e','m','e','n','t','s',']','{'
- ,',','n','a','m','e','}','{','c','o','m'
- ,'p','i','l','a','t','i','o','n','_','u'
- ,'n','i','t','}','p','r','a','g','m','a'
- ,'_','h','e','a','d','e','r','c','o','m'
- ,'p','i','l','a','t','i','o','n','_','u'
- ,'n','i','t','c','o','n','t','e','x','t'
- ,'_','c','l','a','u','s','e','l','i','b'
- ,'r','a','r','y','_','o','r','_','s','e'
- ,'c','o','n','d','a','r','y','_','u','n'
- ,'i','t','s','u','b','u','n','i','t','{'
- ,'w','i','t','h','_','c','l','a','u','s'
- ,'e','{','u','s','e','_','c','l','a','u'
- ,'s','e','}','}','w','i','t','h','_','i'
- ,'d','{',',','w','i','t','h','_','i','d'
- ,'_','l','i','s','t','}','w','i','t','h'
- ,'_','c','l','a','u','s','e','b','o','d'
- ,'y','_','n','a','m','e','e','x','c','e'
- ,'p','t','i','o','n','_','c','h','o','i'
- ,'c','e','{','|','e','x','c','e','p','t'
- ,'i','o','n','_','c','h','o','i','c','e'
- ,'}','e','x','c','e','p','t','i','o','n'
- ,'_','h','a','n','d','l','e','r','g','e'
- ,'n','e','r','i','c','_','s','p','e','c'
- ,'i','f','i','c','a','t','i','o','n','g'
- ,'e','n','e','r','i','c','_','f','o','r'
- ,'m','a','l','_','p','a','r','t','{','g'
- ,'e','n','e','r','i','c','_','p','a','r'
- ,'a','m','e','t','e','r','_','d','e','c'
- ,'l','a','r','a','t','i','o','n','}','g'
- ,'e','n','e','r','i','c','_','p','a','r'
- ,'a','m','e','t','e','r','_','d','e','c'
- ,'l','a','r','a','t','i','o','n','g','e'
- ,'n','e','r','i','c','_','t','y','p','e'
- ,'_','d','e','f','i','n','i','t','i','o'
- ,'n','[','I','S','_','_','n','a','m','e'
- ,'_','_','o','r','_','_','<','>',']','g'
- ,'e','n','e','r','i','c','_','n','a','m'
- ,'e','g','e','n','e','r','i','c','_','a'
- ,'s','s','o','c','i','a','t','i','o','n'
- ,'{',',','g','e','n','e','r','i','c','_'
- ,'a','s','s','o','c','i','a','t','i','o'
- ,'n','}','[','g','e','n','e','r','i','c'
- ,'_','f','o','r','m','a','l','_','p','a'
- ,'r','a','m','e','t','e','r','=','>',']'
- ,'g','e','n','e','r','i','c','_','a','c'
- ,'t','u','a','l','_','p','a','r','a','m'
- ,'e','t','e','r','g','e','n','e','r','i'
- ,'c','_','f','o','r','m','a','l','_','p'
- ,'a','r','a','m','e','t','e','r','g','e'
- ,'n','e','r','i','c','_','a','c','t','u'
- ,'a','l','_','p','a','r','a','m','e','t'
- ,'e','r','l','e','n','g','t','h','_','c'
- ,'l','a','u','s','e','e','n','u','m','e'
- ,'r','a','t','i','o','n','_','r','e','p'
- ,'r','e','s','e','n','t','a','t','i','o'
- ,'n','_','c','l','a','u','s','e','a','d'
- ,'d','r','e','s','s','_','c','l','a','u'
- ,'s','e','r','e','c','o','r','d','_','r'
- ,'e','p','r','e','s','e','n','t','a','t'
- ,'i','o','n','_','c','l','a','u','s','e'
- ,'{','c','o','m','p','o','n','e','n','t'
- ,'_','c','l','a','u','s','e','}','a','l'
- ,'i','g','n','m','e','n','t','_','c','l'
- ,'a','u','s','e','c','o','m','p','o','n'
- ,'e','n','t','_','c','l','a','u','s','e'
- ,'g','a','_','e','x','p','r','e','s','s'
- ,'i','o','n','{','|','i','d','e','n','t'
- ,'i','f','i','e','r','}','e','x','c','e'
- ,'p','t','i','o','n','_','h','a','n','d'
- ,'l','e','r','_','l','i','s','t','u','s'
- ,'e','_','c','l','a','u','s','e','_','l'
- ,'i','s','t') ;
- --| Table of symbols used in the grammar.
- -- NYU Reference Name: NO_SYM
-
- LeftHandSide :
- constant array (LeftHandSideRange)
- of GrammarSymbolRange :=
- ( 101, 101, 99, 103, 103, 103, 103, 103, 103, 103
- , 103, 103, 103, 103, 102, 102, 102, 102, 104, 114
- , 105, 105, 105, 120, 120, 123, 123, 123, 123, 123
- , 123, 123, 106, 115, 115, 133, 134, 134, 134, 134
- , 132, 136, 136, 126, 140, 142, 142, 127, 128, 128
- , 137, 143, 138, 145, 129, 129, 146, 117, 147, 149
- , 151, 151, 153, 153, 130, 154, 154, 154, 157, 124
- , 158, 160, 160, 162, 162, 162, 131, 121, 121, 165
- , 165, 168, 168, 168, 171, 171, 171, 171, 171, 171
- , 171, 166, 166, 172, 172, 172, 150, 150, 150, 150
- , 150, 150, 177, 178, 178, 180, 180, 180, 179, 181
- , 181, 181, 181, 183, 182, 182, 182, 182, 182, 182
- , 100, 100, 100, 118, 118, 118, 118, 118, 118, 192
- , 192, 139, 202, 205, 205, 207, 203, 203, 203, 203
- , 203, 203, 203, 210, 210, 210, 210, 210, 210, 211
- , 211, 211, 212, 212, 206, 206, 213, 213, 213, 213
- , 214, 209, 209, 208, 208, 208, 208, 219, 217, 217
- , 217, 217, 220, 220, 220, 220, 220, 220, 220, 220
- , 220, 220, 221, 221, 221, 221, 221, 221, 239, 223
- , 224, 233, 243, 234, 245, 245, 235, 235, 249, 249
- , 249, 251, 250, 250, 236, 236, 225, 225, 225, 225
- , 226, 226, 227, 107, 254, 254, 254, 254, 255, 258
- , 258, 256, 259, 259, 260, 260, 260, 174, 232, 108
- , 262, 262, 175, 175, 263, 264, 122, 122, 122, 122
- , 170, 113, 113, 113, 113, 109, 266, 266, 266, 266
- , 176, 270, 237, 237, 228, 238, 238, 238, 272, 275
- , 275, 277, 277, 277, 278, 279, 280, 273, 274, 229
- , 98, 284, 285, 285, 285, 287, 287, 287, 287, 287
- , 287, 287, 286, 292, 290, 291, 291, 173, 173, 173
- , 288, 111, 296, 294, 294, 230, 230, 110, 297, 297
- , 298, 300, 300, 300, 300, 301, 301, 301, 301, 301
- , 301, 301, 301, 112, 112, 112, 112, 112, 112, 304
- , 307, 307, 308, 169, 169, 169, 169, 309, 310, 312
- , 312, 315, 314, 311, 231, 155, 155, 159, 159, 216
- , 216, 244, 244, 116, 116, 119, 119, 135, 215, 215
- , 293, 293, 303, 303, 141, 141, 144, 144, 148, 148
- , 152, 152, 156, 156, 125, 125, 161, 161, 163, 163
- , 164, 164, 167, 167, 184, 184, 186, 187, 187, 185
- , 185, 188, 316, 316, 316, 189, 189, 190, 191, 191
- , 317, 317, 193, 193, 194, 194, 195, 195, 196, 196
- , 197, 197, 198, 198, 199, 199, 200, 200, 200, 201
- , 201, 204, 204, 218, 218, 222, 222, 240, 241, 241
- , 242, 242, 246, 246, 247, 247, 248, 248, 253, 253
- , 252, 318, 318, 257, 257, 261, 261, 261, 265, 265
- , 267, 267, 268, 268, 269, 269, 269, 269, 271, 271
- , 271, 271, 276, 276, 281, 281, 282, 282, 283, 283
- , 289, 289, 319, 319, 295, 295, 299, 299, 302, 302
- , 302, 305, 305, 306, 306, 313, 313) ;
- --| Map of the grammar rule number (constant array ) to
- --| numeric value of left hand side symbol.
- -- NYU Reference Name: LHS
-
- RightHandSide :
- constant array (RightHandSideRange)
- of GC.ParserInteger :=
- ( 6, 3, 1, 1, 1, 1, 1, 1, 1, 1
- , 1, 1, 1, 1, 5, 6, 5, 6, 6, 2
- , 1, 1, 1, 5, 9, 1, 1, 1, 1, 1
- , 1, 1, 5, 1, 2, 1, 1, 1, 1, 3
- , 2, 2, 4, 4, 1, 1, 1, 1, 1, 1
- , 2, 2, 2, 2, 1, 1, 7, 4, 3, 4
- , 2, 1, 1, 3, 4, 4, 4, 3, 5, 4
- , 9, 5, 4, 1, 3, 2, 2, 3, 7, 1
- , 3, 1, 1, 1, 1, 1, 1, 1, 1, 1
- , 1, 1, 1, 1, 1, 1, 1, 1, 1, 1
- , 1, 1, 4, 3, 3, 1, 1, 1, 3, 1
- , 1, 1, 1, 3, 2, 5, 5, 3, 3, 1
- , 1, 4, 2, 1, 1, 1, 1, 1, 1, 2
- , 3, 1, 1, 2, 2, 3, 1, 1, 1, 1
- , 1, 1, 1, 1, 1, 1, 1, 1, 1, 1
- , 1, 1, 1, 1, 1, 1, 1, 1, 1, 1
- , 1, 3, 3, 2, 5, 4, 4, 3, 1, 1
- , 2, 2, 1, 1, 1, 1, 1, 1, 1, 1
- , 1, 1, 1, 1, 1, 1, 1, 1, 3, 2
- , 4, 7, 1, 9, 5, 4, 7, 8, 2, 4
- , 5, 2, 3, 5, 5, 4, 2, 4, 3, 5
- , 2, 3, 3, 2, 2, 6, 4, 8, 1, 1
- , 1, 4, 1, 2, 1, 2, 3, 5, 2, 2
- , 5, 7, 6, 5, 2, 3, 6, 10, 5, 9
- , 4, 6, 6, 5, 4, 2, 2, 3, 7, 8
- , 7, 4, 4, 8, 3, 1, 1, 1, 7, 5
- , 2, 1, 1, 1, 2, 2, 3, 9, 10, 4
- , 1, 2, 5, 2, 2, 1, 1, 1, 1, 1
- , 1, 1, 1, 4, 1, 0, 3, 4, 4, 6
- , 5, 4, 5, 1, 1, 2, 3, 2, 2, 2
- , 2, 5, 5, 9, 4, 3, 2, 2, 2, 2
- , 1, 1, 1, 5, 9, 6, 10, 5, 9, 1
- , 1, 1, 1, 1, 1, 1, 1, 5, 5, 8
- , 9, 5, 4, 6, 4, 0, 2, 0, 2, 0
- , 2, 0, 2, 0, 2, 0, 3, 1, 1, 3
- , 1, 3, 1, 3, 0, 3, 0, 1, 0, 3
- , 0, 3, 0, 3, 0, 3, 0, 2, 0, 3
- , 1, 3, 1, 3, 3, 3, 4, 0, 3, 0
- , 2, 3, 1, 3, 2, 1, 3, 4, 0, 3
- , 0, 3, 3, 3, 3, 3, 3, 3, 4, 4
- , 4, 4, 0, 2, 1, 2, 1, 2, 3, 1
- , 3, 0, 2, 1, 3, 1, 2, 3, 0, 5
- , 0, 2, 0, 2, 0, 2, 0, 1, 0, 2
- , 2, 1, 2, 0, 3, 0, 1, 1, 0, 3
- , 1, 3, 0, 3, 0, 4, 3, 7, 0, 4
- , 3, 7, 0, 3, 1, 1, 0, 3, 1, 2
- , 0, 3, 1, 3, 0, 3, 0, 2, 0, 2
- , 2, 0, 3, 1, 3, 1, 3) ;
- --| Map of the grammar rule number (constant array ) to
- --| size of right hand sides (number of symbols).
- -- NYU Reference Name: RHS
-
- ActionTableOne :
- constant array (ActionTableOneRange)
- of GC.ParserInteger :=
- ( 41, 42, 6948, 627, 6951, 99, 441, 6954, 6957, 6960
- , 65, 6963, 6966, 67, 68, 69, 6969, 0, 6973, 6976
- , 41, 42, 0, 0, 43, 0, 0, 6979, 0, 45
- , 6982, 273, 6985, 42, 6988, 0, 0, 733, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 746, 0, 0
- , 0, 35, 0, 0, 0, 0, 0, 6991, 0, 0
- , 0, 421, 0, 858, 0, 0, 6994, 0, 0, 662
- , 0, 6997, 222, 0, 927, 0, 0, 0, 0, 0
- , 168, 0, 0, 7000, 37, 7003, 0, 515, 871, 7006
- , 7009, 433, 222, 0, 35, 0, 0, 0, 0, 0
- , 0, 0, 0, 152, 528, 0, 0, 0, 0, 0
- , 7012, 51, 52, 103, 7015, 7018, 7021, 0, 0, 43
- , 0, 0, 44, 0, 7025, 7028, 36, 37, 7032, 1380
- , 50, 7035, 7038, 7041, 63, 64, 7044, 0, 66, 67
- , 7047, 69, 7050, 7054, 7057, 7060, 7063, 7066, 7069, 60
- , 61, 0, 0, 7073, 63, 64, 7076, 40, 7081, 7084
- , 7088, 7091, 7094, 0, 0, 7097, 0, 45, 0, 0
- , 0, 283, 7100, 7103, 7106, 42, 7110, 7114, 7117, 42
- , 0, 7120, 7123, 45, 0, 7126, 7130, 7133, 7139, 7142
- , 7145, 7148, 487, 488, 489, 7152, 7155, 7158, 7161, 7165
- , 495, 496, 497, 7168, 499, 0, 0, 859, 0, 314
- , 872, 0, 7171, 0, 295, 17, 0, 167, 501, 0
- , 0, 0, 0, 0, 0, 7174, 7178, 52, 0, 7181
- , 7184, 53, 0, 0, 0, 160, 0, 502, 7187, 504
- , 0, 7190, 0, 0, 0, 0, 222, 0, 62, 7193
- , 7196, 65, 0, 7199, 67, 68, 69, 7203, 0, 0
- , 71, 152, 0, 0, 0, 684, 0, 0, 50, 51
- , 52, 0, 255, 256, 7206, 258, 259, 7211, 261, 7215
- , 7219, 264, 265, 7222, 7226, 7230, 7233, 60, 7236, 51
- , 7239, 7243, 7246, 64, 7250, 0, 66, 67, 68, 7253
- , 7256, 58, 7259, 7262, 7266, 58, 59, 7269, 7272, 64
- , 65, 7275, 7278, 7283, 7287, 69, 7292, 67, 68, 7295
- , 70, 0, 359, 71, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 272, 273
- , 274, 0, 427, 40, 428, 42, 0, 231, 43, 0
- , 535, 44, 0, 7298, 0, 0, 0, 0, 0, 0
- , 0, 7301, 0, 2, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 7304, 884, 0, 0, 0, 0, 0
- , 0, 0, 236, 0, 99, 0, 0, 0, 0, 676
- , 0, 0, 0, 0, 0, 429, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 35, 0, 222, 665, 3, 640
- , 666, 0, 0, 529, 297, 0, 0, 152, 7307, 103
- , 35, 7310, 7313, 27, 35, 0, 282, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 36, 37, 38, 0
- , 0, 0, 0, 0, 50, 51, 7316, 0, 0, 0
- , 53, 0, 36, 37, 7319, 685, 36, 7323, 7326, 56
- , 57, 58, 59, 60, 61, 0, 103, 7330, 7333, 7336
- , 7340, 285, 7343, 67, 68, 7347, 7350, 45, 0, 71
- , 0, 0, 7353, 7356, 7359, 42, 103, 40, 7362, 42
- , 287, 44, 43, 45, 0, 44, 0, 45, 0, 126
- , 127, 298, 79, 0, 824, 0, 7365, 0, 0, 619
- , 0, 0, 114, 0, 345, 7368, 0, 0, 707, 0
- , 0, 907, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 50, 51, 52, 0, 686, 0, 97, 0, 0
- , 7371, 0, 0, 0, 0, 0, 0, 36, 7374, 38
- , 0, 7377, 0, 0, 0, 0, 589, 115, 116, 117
- , 7380, 1024, 191, 0, 0, 7383, 120, 7386, 0, 0
- , 0, 7389, 509, 431, 432, 433, 0, 103, 7392, 7396
- , 7399, 919, 0, 43, 7402, 0, 44, 0, 45, 0
- , 0, 0, 0, 4, 7405, 7408, 7411, 0, 50, 7414
- , 7417, 62, 7420, 64, 7424, 98, 7428, 7431, 68, 69
- , 70, 0, 575, 71, 0, 0, 0, 62, 63, 64
- , 7434, 62, 7437, 7441, 7444, 69, 7448, 67, 68, 7451
- , 70, 0, 0, 71, 0, 0, 0, 35, 0, 0
- , 0, 0, 444, 0, 0, 0, 0, 0, 0, 0
- , 0, 7454, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 152, 0, 97, 0, 0, 0, 0, 36
- , 37, 7457, 0, 238, 122, 123, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 124, 100, 0, 7461
- , 7464, 52, 0, 0, 0, 7467, 0, 0, 0, 7470
- , 40, 41, 42, 0, 0, 43, 0, 0, 0, 0
- , 0, 0, 62, 63, 7473, 65, 0, 66, 67, 68
- , 7476, 70, 7479, 0, 71, 0, 101, 0, 0, 10
- , 7482, 379, 520, 0, 99, 0, 0, 0, 0, 0
- , 0, 0, 7485, 284, 285, 286, 0, 0, 0, 0
- , 642, 0, 36, 37, 38, 0, 0, 0, 0, 0
- , 0, 205, 206, 0, 0, 0, 318, 920, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 530
- , 0, 0, 103, 40, 7488, 42, 0, 0, 7491, 0
- , 0, 44, 207, 45, 0, 0, 0, 0, 590, 0
- , 179, 0, 97, 0, 0, 0, 0, 0, 0, 0
- , 208, 50, 51, 7494, 237, 239, 538, 7497, 0, 0
- , 0, 422, 0, 0, 810, 0, 299, 0, 0, 754
- , 0, 0, 547, 548, 0, 63, 7500, 7503, 0, 66
- , 67, 68, 69, 7506, 0, 0, 0, 0, 0, 516
- , 0, 0, 0, 0, 0, 0, 201, 0, 180, 0
- , 0, 0, 0, 125, 0, 299, 7509, 7512, 0, 97
- , 202, 0, 0, 128, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 893, 0, 0, 577, 0, 0
- , 0, 577, 0, 0, 50, 51, 7516, 0, 0, 446
- , 53, 0, 0, 0, 7519, 0, 0, 0, 0, 0
- , 0, 0, 772, 0, 448, 0, 0, 62, 63, 64
- , 65, 0, 66, 67, 7522, 69, 7525, 0, 708, 71
- , 0, 0, 192, 0, 836, 0, 0, 346, 0, 99
- , 78, 0, 0, 0, 240, 0, 362, 0, 0, 0
- , 578, 0, 7528, 580, 7532, 0, 7536, 580, 581, 565
- , 0, 566, 0, 565, 0, 566, 0, 0, 97, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 77, 0, 0, 0, 0, 0, 735, 0, 0
- , 0, 0, 0, 0, 0, 930, 0, 0, 0, 0
- , 0, 1047, 0, 401, 0, 0, 449, 0, 450, 908
- , 0, 0, 0, 0, 921, 0, 0, 0, 0, 237
- , 0, 0, 811, 0, 7539, 0, 99, 0, 1047, 0
- , 1047, 0, 0, 1047, 0, 0, 0, 0, 0, 0
- , 35, 1047, 0, 1047, 0, 0, 950, 0, 300, 0
- , 0, 0, 0, 0, 644, 645, 0, 0, 1047, 0
- , 0, 0, 0, 1047, 7542, 1047, 7545, 1047, 1047, 1296
- , 1047, 1047, 7548, 7551, 38, 1047, 1047, 1047, 0, 0
- , 1047, 1047, 0, 1047, 1047, 1047, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 36, 37, 38, 0
- , 0, 102, 103, 40, 7554, 42, 237, 0, 43, 0
- , 0, 44, 0, 7557, 0, 0, 0, 0, 678, 0
- , 179, 791, 97, 0, 0, 318, 7560, 7563, 41, 42
- , 79, 0, 43, 0, 0, 44, 0, 45, 299, 0
- , 0, 0, 0, 35, 0, 0, 97, 35, 0, 755
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 156, 0, 0, 0, 36, 7566, 38, 180, 7569
- , 37, 38, 0, 0, 0, 0, 0, 152, 0, 0
- , 0, 157, 0, 0, 847, 0, 0, 0, 0, 0
- , 105, 0, 0, 0, 0, 103, 7572, 41, 42, 7575
- , 40, 7578, 42, 0, 7582, 7585, 7588, 0, 44, 0
- , 7591, 0, 0, 107, 7594, 88, 0, 801, 748, 0
- , 0, 0, 0, 0, 0, 0, 940, 62, 7598, 7602
- , 7605, 0, 66, 7609, 7612, 7617, 70, 110, 0, 7620
- , 0, 0, 0, 56, 7623, 58, 59, 7626, 61, 0
- , 0, 7629, 7633, 7636, 65, 0, 66, 67, 68, 69
- , 70, 0, 593, 71, 0, 0, 0, 0, 0, 7639
- , 0, 0, 0, 222, 0, 0, 7642, 7645, 0, 0
- , 629, 630, 0, 631, 152, 0, 7648, 1411, 0, 0
- , 0, 425, 0, 0, 0, 0, 0, 0, 0, 436
- , 127, 0, 7651, 2, 0, 1411, 128, 7654, 51, 52
- , 0, 7657, 51, 7660, 1411, 0, 0, 53, 0, 0
- , 0, 0, 0, 1411, 0, 0, 7663, 57, 58, 59
- , 7666, 7669, 64, 65, 62, 7672, 7675, 7678, 69, 7681
- , 67, 68, 7684, 70, 0, 0, 71, 0, 0, 0
- , 7687, 0, 0, 0, 436, 127, 7690, 0, 0, 0
- , 0, 128, 0, 0, 0, 909, 874, 0, 0, 0
- , 35, 347, 0, 185, 0, 0, 825, 688, 35, 0
- , 0, 0, 7693, 37, 38, 0, 0, 0, 539, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 36, 37, 38, 0, 0, 134, 0, 0
- , 36, 37, 7696, 40, 41, 42, 0, 0, 43, 0
- , 0, 44, 0, 45, 0, 0, 0, 0, 160, 1047
- , 0, 0, 103, 40, 41, 42, 0, 0, 43, 0
- , 103, 7699, 41, 7702, 0, 0, 43, 0, 0, 44
- , 0, 7706, 1047, 0, 0, 0, 1047, 0, 1047, 756
- , 88, 1047, 0, 0, 0, 0, 0, 0, 0, 1047
- , 0, 1047, 0, 0, 0, 0, 348, 238, 0, 17
- , 0, 0, 0, 0, 0, 594, 7709, 0, 632, 0
- , 349, 1047, 1047, 7712, 1047, 1047, 1047, 7715, 7718, 1047
- , 1047, 0, 0, 1047, 1047, 1047, 7721, 1341, 1047, 1047
- , 0, 1047, 1047, 1047, 222, 0, 0, 152, 0, 0
- , 0, 0, 0, 0, 50, 7724, 52, 0, 0, 0
- , 53, 103, 0, 41, 42, 0, 0, 0, 813, 0
- , 0, 205, 206, 0, 7727, 7730, 7733, 7736, 7739, 7742
- , 7745, 0, 7749, 7752, 7755, 69, 70, 0, 53, 7758
- , 57, 58, 7762, 7765, 61, 0, 17, 7768, 7771, 7774
- , 7777, 60, 7780, 67, 68, 7784, 7787, 7790, 65, 71
- , 7793, 7796, 7799, 69, 70, 168, 0, 71, 0, 0
- , 208, 35, 0, 0, 173, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 350, 7802, 277, 278
- , 7805, 0, 0, 7809, 0, 0, 849, 0, 0, 518
- , 0, 0, 0, 36, 37, 7812, 0, 371, 7815, 453
- , 454, 455, 0, 456, 0, 0, 0, 0, 180, 0
- , 0, 0, 0, 50, 51, 52, 0, 0, 0, 0
- , 0, 12, 0, 103, 40, 41, 42, 875, 0, 43
- , 13, 0, 0, 0, 327, 0, 0, 0, 0, 0
- , 135, 0, 0, 0, 35, 0, 0, 0, 0, 0
- , 0, 0, 0, 205, 206, 0, 0, 457, 7818, 0
- , 0, 7821, 459, 275, 276, 277, 278, 279, 28, 0
- , 0, 0, 0, 0, 0, 0, 7824, 37, 38, 0
- , 0, 102, 0, 0, 207, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 208, 0, 0, 0, 103, 40, 7827, 7832
- , 0, 0, 43, 0, 0, 44, 179, 45, 97, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 838, 0, 0, 0, 7835, 51, 7839, 0, 0
- , 0, 7842, 860, 0, 0, 460, 185, 0, 0, 757
- , 0, 0, 0, 26, 27, 281, 0, 282, 0, 7845
- , 232, 65, 0, 66, 67, 68, 7848, 7851, 7854, 38
- , 0, 0, 0, 0, 180, 0, 0, 0, 0, 0
- , 105, 0, 0, 0, 0, 0, 520, 0, 7857, 7860
- , 839, 7863, 0, 0, 0, 301, 0, 39, 40, 41
- , 7866, 0, 0, 7869, 0, 689, 7872, 0, 45, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 7875, 51
- , 7879, 185, 0, 0, 7882, 160, 177, 321, 0, 322
- , 0, 0, 510, 56, 57, 58, 59, 60, 7885, 37
- , 38, 62, 63, 64, 7888, 0, 66, 67, 7891, 69
- , 7894, 7898, 38, 71, 179, 0, 840, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 7901, 40
- , 41, 7904, 0, 0, 7907, 0, 0, 44, 243, 45
- , 103, 40, 7910, 42, 0, 0, 43, 0, 0, 44
- , 0, 45, 103, 0, 41, 42, 0, 0, 0, 0
- , 0, 196, 0, 680, 0, 155, 0, 0, 0, 50
- , 51, 52, 180, 0, 0, 53, 0, 0, 0, 0
- , 0, 7913, 55, 0, 56, 7916, 58, 7919, 60, 61
- , 0, 0, 62, 63, 64, 65, 0, 66, 67, 68
- , 69, 70, 222, 0, 71, 157, 0, 0, 0, 0
- , 0, 0, 0, 152, 540, 0, 0, 0, 0, 0
- , 35, 179, 0, 0, 0, 152, 372, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 738, 0, 0
- , 50, 51, 52, 0, 0, 0, 53, 464, 0, 465
- , 774, 0, 7922, 7926, 7929, 7932, 0, 466, 53, 1379
- , 467, 0, 0, 62, 7935, 7939, 7943, 0, 7947, 7950
- , 7953, 69, 70, 469, 470, 7956, 7959, 64, 7962, 477
- , 66, 67, 7965, 7969, 7972, 42, 0, 71, 43, 0
- , 0, 7976, 0, 45, 0, 0, 473, 0, 474, 0
- , 0, 0, 97, 0, 521, 0, 1118, 1375, 72, 0
- , 475, 0, 41, 42, 0, 0, 0, 7979, 185, 7982
- , 0, 649, 931, 620, 0, 0, 0, 0, 0, 0
- , 0, 621, 0, 0, 0, 47, 861, 7985, 0, 0
- , 403, 0, 0, 0, 0, 0, 0, 0, 404, 405
- , 0, 0, 0, 0, 0, 799, 48, 0, 0, 0
- , 0, 0, 0, 0, 406, 7988, 0, 49, 0, 0
- , 0, 0, 0, 0, 0, 0, 407, 0, 0, 408
- , 0, 0, 522, 0, 0, 0, 35, 511, 0, 0
- , 373, 0, 512, 827, 50, 7991, 52, 0, 0, 304
- , 53, 185, 739, 409, 691, 926, 54, 55, 749, 56
- , 57, 58, 59, 60, 61, 0, 0, 62, 7994, 7997
- , 8000, 0, 8003, 8006, 8009, 69, 8012, 0, 0, 71
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 461, 0, 0, 103, 8015
- , 41, 42, 599, 0, 43, 0, 0, 44, 0, 45
- , 97, 411, 710, 412, 0, 480, 481, 8018, 8021, 484
- , 8024, 8027, 487, 488, 489, 490, 8030, 8033, 8036, 494
- , 495, 496, 497, 8039, 499, 0, 0, 0, 0, 0
- , 0, 0, 8042, 35, 0, 17, 0, 0, 501, 0
- , 0, 0, 465, 932, 8045, 0, 0, 0, 0, 0
- , 0, 0, 0, 8048, 0, 0, 0, 8051, 503, 8054
- , 0, 0, 222, 0, 0, 36, 37, 38, 0, 0
- , 0, 0, 0, 8057, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 213, 0, 0, 168, 0, 0, 0
- , 0, 0, 0, 681, 0, 8060, 8065, 8068, 8071, 0
- , 8074, 8078, 8081, 0, 44, 0, 8085, 0, 161, 0
- , 0, 0, 0, 0, 0, 334, 0, 0, 0, 0
- , 50, 51, 52, 62, 63, 64, 65, 0, 66, 67
- , 68, 69, 8088, 37, 38, 71, 0, 137, 0, 0
- , 0, 0, 214, 0, 215, 216, 0, 0, 594, 0
- , 541, 0, 0, 0, 0, 0, 323, 0, 0, 0
- , 396, 0, 103, 40, 8091, 8094, 354, 373, 43, 8097
- , 788, 8100, 0, 8103, 725, 0, 0, 600, 0, 0
- , 152, 650, 171, 0, 0, 0, 0, 523, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 35
- , 0, 911, 0, 36, 37, 38, 0, 50, 51, 8106
- , 0, 0, 0, 53, 0, 601, 0, 0, 0, 0
- , 0, 0, 56, 57, 58, 59, 60, 61, 0, 0
- , 62, 8109, 8112, 8115, 40, 8119, 8123, 68, 69, 8127
- , 0, 354, 8130, 0, 8133, 0, 0, 152, 0, 0
- , 0, 0, 26, 27, 28, 0, 0, 217, 0, 0
- , 740, 103, 8138, 41, 42, 299, 8141, 43, 814, 0
- , 44, 0, 8145, 775, 50, 8148, 52, 29, 30, 0
- , 53, 0, 0, 0, 0, 0, 0, 31, 32, 56
- , 57, 58, 59, 60, 8151, 0, 0, 62, 8154, 8157
- , 8160, 0, 66, 67, 68, 69, 70, 389, 0, 71
- , 0, 83, 93, 0, 0, 876, 8163, 704, 8166, 42
- , 97, 0, 0, 0, 299, 0, 0, 0, 39, 40
- , 8170, 42, 0, 35, 43, 201, 299, 8173, 0, 45
- , 0, 0, 190, 0, 0, 50, 8176, 8179, 0, 631
- , 0, 53, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 8182, 0, 36, 37, 38, 62, 8185
- , 8188, 8192, 0, 8195, 8199, 8202, 69, 70, 0, 8205
- , 71, 47, 0, 923, 0, 0, 0, 0, 520, 0
- , 99, 0, 0, 726, 0, 427, 8208, 8211, 8215, 8218
- , 8221, 8224, 8229, 68, 8233, 8236, 45, 0, 8239, 0
- , 45, 0, 0, 49, 0, 828, 126, 127, 0, 0
- , 436, 127, 0, 128, 0, 0, 0, 128, 50, 51
- , 8242, 0, 0, 0, 0, 0, 0, 0, 0, 345
- , 50, 51, 52, 0, 0, 0, 53, 0, 8245, 0
- , 398, 0, 8248, 55, 0, 8251, 57, 58, 59, 60
- , 61, 0, 0, 62, 63, 64, 65, 0, 66, 8254
- , 8257, 69, 70, 222, 0, 8260, 0, 0, 0, 0
- , 152, 815, 727, 0, 8264, 0, 0, 0, 0, 0
- , 0, 35, 0, 0, 0, 0, 0, 0, 0, 436
- , 127, 0, 0, 0, 0, 0, 128, 8267, 8272, 8275
- , 0, 50, 8279, 8282, 0, 0, 0, 53, 0, 789
- , 0, 0, 56, 8285, 8288, 8291, 8294, 8298, 58, 59
- , 8301, 8304, 64, 65, 62, 8307, 8310, 8313, 8318, 8321
- , 8325, 68, 8328, 8331, 0, 97, 8334, 0, 45, 356
- , 0, 8337, 42, 103, 40, 41, 8340, 0, 0, 43
- , 0, 0, 44, 0, 45, 0, 0, 323, 0, 163
- , 0, 0, 0, 0, 373, 0, 168, 877, 0, 72
- , 0, 0, 0, 0, 0, 169, 170, 0, 0, 0
- , 104, 0, 863, 0, 0, 0, 851, 0, 179, 829
- , 0, 0, 34, 0, 0, 898, 8343, 0, 0, 180
- , 0, 105, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 106, 0, 160, 463, 0, 222, 0, 0
- , 0, 84, 0, 602, 8346, 0, 431, 432, 8350, 0
- , 0, 0, 0, 0, 0, 0, 125, 0, 0, 50
- , 51, 52, 0, 0, 108, 53, 8354, 0, 110, 0
- , 111, 50, 51, 358, 8358, 8361, 8364, 8367, 60, 61
- , 0, 8370, 8373, 8376, 64, 65, 0, 8379, 67, 68
- , 8382, 8385, 58, 59, 8388, 61, 0, 0, 62, 63
- , 64, 65, 603, 66, 67, 8391, 8394, 70, 0, 0
- , 71, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 434, 0, 0, 0, 0
- , 35, 0, 0, 0, 0, 0, 168, 0, 0, 0
- , 0, 0, 0, 0, 532, 8397, 174, 0, 0, 0
- , 0, 0, 0, 0, 0, 692, 0, 0, 0, 0
- , 0, 0, 8400, 37, 38, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 816, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 525, 0, 0
- , 0, 0, 39, 40, 41, 42, 0, 0, 43, 0
- , 0, 44, 0, 45, 97, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 8403, 604, 0, 8406, 0
- , 0, 759, 175, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 912, 0, 0, 47, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 48, 0, 0, 0
- , 0, 0, 399, 0, 99, 0, 0, 8409, 0, 359
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 662, 693, 0, 0, 0, 776, 0, 0, 777
- , 0, 0, 633, 0, 8412, 51, 8415, 0, 191, 0
- , 53, 0, 85, 0, 0, 0, 0, 218, 0, 56
- , 8418, 8421, 59, 60, 61, 0, 852, 62, 8424, 64
- , 65, 0, 66, 67, 68, 69, 8427, 0, 0, 71
- , 0, 0, 0, 0, 0, 181, 0, 0, 0, 0
- , 0, 0, 0, 0, 237, 0, 0, 0, 0, 0
- , 36, 8430, 38, 0, 0, 306, 0, 0, 0, 0
- , 0, 35, 0, 0, 0, 0, 0, 8434, 0, 0
- , 0, 624, 0, 0, 0, 0, 97, 0, 0, 0
- , 103, 40, 41, 42, 0, 0, 43, 0, 0, 44
- , 0, 45, 0, 36, 37, 38, 0, 0, 945, 8437
- , 0, 0, 465, 899, 0, 0, 0, 0, 653, 0
- , 0, 0, 0, 467, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 103, 40, 41, 42, 0, 0, 43
- , 0, 0, 0, 219, 0, 0, 0, 0, 0, 0
- , 0, 179, 0, 0, 0, 182, 0, 0, 0, 0
- , 0, 0, 0, 0, 201, 696, 0, 0, 0, 8440
- , 0, 0, 0, 0, 0, 674, 842, 0, 631, 0
- , 0, 0, 0, 0, 830, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 50, 51, 52, 0, 0, 0, 53, 477
- , 0, 0, 140, 0, 179, 0, 0, 141, 152, 142
- , 0, 0, 220, 0, 0, 62, 63, 64, 65, 0
- , 66, 67, 8443, 8446, 70, 0, 792, 71, 0, 0
- , 711, 0, 0, 0, 0, 50, 51, 52, 0, 0
- , 0, 53, 665, 0, 760, 8449, 199, 0, 821, 761
- , 0, 0, 0, 913, 0, 36, 37, 38, 0, 0
- , 0, 8452, 180, 233, 67, 68, 69, 70, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 900, 0, 0, 0, 39, 40, 41, 42, 360
- , 0, 43, 0, 0, 44, 0, 45, 0, 0, 0
- , 0, 0, 0, 0, 0, 793, 776, 0, 0, 777
- , 0, 0, 0, 464, 0, 465, 0, 864, 0, 668
- , 307, 8455, 86, 466, 0, 1379, 8458, 0, 0, 0
- , 0, 0, 0, 0, 0, 8461, 8464, 0, 47, 469
- , 470, 0, 0, 0, 8467, 0, 0, 0, 8470, 946
- , 0, 0, 0, 0, 179, 0, 0, 472, 0, 48
- , 0, 0, 473, 0, 474, 0, 0, 0, 8473, 0
- , 49, 8476, 0, 1375, 0, 702, 8479, 704, 8483, 42
- , 0, 0, 0, 0, 97, 0, 0, 0, 0, 0
- , 0, 582, 0, 0, 0, 0, 0, 50, 51, 52
- , 0, 0, 0, 8487, 0, 0, 0, 0, 0, 54
- , 55, 0, 8490, 57, 58, 8493, 60, 61, 0, 0
- , 62, 63, 64, 65, 0, 66, 67, 68, 69, 70
- , 0, 0, 71, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 164, 0, 0, 0, 0
- , 435, 0, 0, 0, 0, 0, 0, 0, 0, 78
- , 35, 478, 0, 0, 0, 0, 0, 0, 0, 0
- , 545, 97, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 144, 50, 51
- , 52, 0, 8496, 37, 38, 0, 0, 0, 0, 0
- , 0, 0, 8499, 654, 0, 8503, 0, 0, 0, 0
- , 0, 0, 0, 547, 548, 221, 0, 0, 0, 0
- , 0, 729, 103, 40, 8506, 8510, 8513, 0, 8516, 865
- , 0, 8519, 8523, 8526, 8529, 484, 8532, 486, 487, 8535
- , 489, 8538, 491, 492, 8543, 8546, 495, 8549, 497, 8552
- , 499, 0, 0, 0, 762, 8555, 41, 42, 500, 0
- , 43, 0, 0, 44, 501, 45, 0, 526, 553, 0
- , 0, 0, 0, 8558, 0, 35, 0, 0, 0, 35
- , 0, 0, 546, 502, 503, 504, 0, 369, 0, 0
- , 0, 0, 0, 0, 0, 0, 8561, 0, 0, 0
- , 935, 0, 373, 8564, 112, 374, 335, 8567, 37, 8571
- , 0, 8574, 37, 38, 410, 0, 0, 0, 0, 0
- , 867, 237, 0, 555, 556, 8577, 8580, 559, 8583, 8586
- , 373, 0, 0, 8589, 8592, 8595, 8598, 103, 40, 8601
- , 8604, 103, 8609, 8612, 42, 0, 44, 43, 45, 8617
- , 44, 547, 8620, 0, 506, 0, 0, 62, 63, 64
- , 8624, 0, 66, 67, 68, 69, 8627, 8632, 52, 71
- , 550, 0, 53, 0, 0, 0, 844, 0, 0, 551
- , 0, 56, 8635, 8638, 8641, 60, 8644, 0, 0, 62
- , 63, 8647, 65, 8650, 66, 8653, 68, 69, 8656, 37
- , 38, 8659, 0, 936, 8662, 0, 553, 0, 0, 752
- , 0, 803, 0, 0, 0, 854, 0, 0, 0, 0
- , 0, 0, 152, 308, 0, 36, 8665, 38, 103, 40
- , 41, 8668, 0, 0, 43, 0, 0, 8671, 0, 45
- , 0, 0, 0, 0, 0, 764, 0, 309, 0, 8674
- , 51, 8677, 410, 50, 51, 8680, 40, 41, 8684, 8687
- , 0, 8690, 556, 557, 8693, 559, 8696, 561, 0, 36
- , 37, 8699, 8702, 8705, 64, 8708, 62, 8711, 8714, 8718
- , 8721, 8726, 67, 68, 8731, 70, 0, 128, 71, 0
- , 46, 879, 0, 0, 402, 0, 8734, 403, 0, 8737
- , 40, 41, 8740, 0, 35, 8743, 405, 0, 8746, 0
- , 45, 0, 36, 8750, 38, 0, 0, 0, 0, 0
- , 0, 406, 0, 0, 0, 937, 0, 765, 0, 48
- , 0, 0, 0, 407, 0, 0, 8753, 37, 38, 0
- , 8756, 8760, 8763, 40, 41, 42, 53, 0, 43, 0
- , 0, 44, 594, 45, 0, 0, 0, 0, 0, 0
- , 409, 0, 0, 62, 63, 64, 8767, 8770, 8774, 8779
- , 8784, 8787, 8791, 8795, 128, 8799, 43, 8802, 169, 8805
- , 55, 45, 56, 57, 8809, 8812, 60, 8815, 0, 766
- , 62, 63, 8818, 65, 0, 66, 67, 68, 69, 70
- , 0, 0, 71, 36, 37, 38, 410, 0, 102, 422
- , 0, 50, 51, 52, 0, 0, 222, 53, 411, 0
- , 412, 0, 249, 594, 0, 310, 56, 8821, 58, 8824
- , 60, 61, 0, 103, 8827, 8830, 8834, 8837, 0, 8840
- , 8844, 68, 8849, 70, 8852, 0, 71, 323, 0, 0
- , 0, 152, 8855, 0, 50, 8858, 8861, 0, 0, 0
- , 8864, 185, 0, 0, 694, 171, 0, 0, 0, 225
- , 0, 0, 0, 0, 0, 0, 0, 8867, 8870, 8873
- , 8876, 0, 8880, 8884, 8887, 69, 70, 166, 53, 71
- , 179, 0, 0, 0, 0, 0, 0, 8891, 57, 58
- , 59, 8894, 8897, 64, 65, 62, 8900, 8905, 8909, 69
- , 8912, 67, 68, 8915, 70, 0, 0, 71, 106, 0
- , 8918, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 107, 0, 717, 0, 0, 0, 0, 0, 0, 0
- , 180, 1047, 0, 0, 0, 50, 51, 8921, 8924, 167
- , 0, 53, 0, 36, 393, 8927, 322, 514, 0, 0
- , 0, 35, 0, 0, 8930, 0, 0, 0, 8933, 8936
- , 8939, 65, 0, 8942, 67, 8945, 69, 70, 0, 567
- , 71, 0, 0, 8948, 40, 41, 42, 329, 0, 8951
- , 8954, 0, 0, 36, 37, 38, 0, 0, 1047, 0
- , 35, 0, 0, 1047, 1047, 1047, 1047, 1047, 1047, 1047
- , 1047, 1047, 1047, 0, 0, 1047, 1047, 1047, 0, 1271
- , 0, 1047, 0, 8957, 8960, 8964, 42, 0, 0, 43
- , 0, 0, 8967, 37, 8970, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 36, 37, 8974, 0
- , 0, 0, 8977, 40, 41, 42, 0, 0, 8980, 168
- , 0, 44, 0, 45, 160, 0, 0, 0, 8983, 170
- , 149, 0, 0, 0, 0, 0, 8986, 40, 41, 42
- , 0, 0, 43, 0, 0, 8989, 51, 8992, 0, 0
- , 0, 53, 113, 0, 0, 0, 0, 436, 8996, 880
- , 0, 631, 330, 0, 128, 0, 0, 0, 0, 0
- , 0, 9000, 0, 415, 0, 68, 69, 70, 0, 0
- , 0, 0, 0, 416, 0, 50, 9004, 52, 0, 0
- , 0, 53, 0, 0, 0, 311, 0, 152, 0, 0
- , 0, 0, 0, 115, 116, 117, 0, 0, 9008, 63
- , 9011, 9015, 120, 9018, 9021, 9024, 9027, 9030, 0, 0
- , 71, 152, 0, 128, 9034, 51, 9037, 0, 0, 0
- , 53, 0, 436, 127, 250, 14, 15, 0, 0, 9040
- , 0, 0, 0, 0, 0, 0, 0, 9043, 9046, 9049
- , 9052, 251, 66, 67, 9055, 69, 9059, 9062, 38, 71
- , 0, 0, 0, 0, 252, 253, 0, 0, 254, 181
- , 0, 62, 63, 64, 9065, 184, 66, 67, 68, 69
- , 70, 87, 185, 9068, 0, 610, 427, 40, 428, 9071
- , 0, 0, 9074, 0, 0, 9077, 0, 45, 0, 0
- , 0, 0, 299, 0, 0, 0, 0, 0, 0, 0
- , 0, 9080, 256, 257, 258, 259, 260, 261, 262, 263
- , 9083, 9086, 266, 9089, 0, 0, 0, 36, 37, 9092
- , 269, 270, 124, 0, 1049, 0, 0, 0, 1049, 429
- , 1049, 0, 0, 1049, 0, 73, 0, 9095, 0, 0
- , 438, 0, 0, 1049, 0, 0, 0, 103, 9098, 9101
- , 9105, 0, 0, 43, 0, 128, 44, 0, 9108, 0
- , 35, 152, 0, 1049, 1049, 9111, 1049, 9114, 9117, 9120
- , 1049, 9123, 9126, 277, 278, 9129, 1049, 1049, 0, 1272
- , 0, 1049, 0, 1049, 1049, 1049, 0, 0, 50, 51
- , 52, 0, 36, 37, 9132, 0, 0, 0, 0, 0
- , 0, 0, 0, 56, 9135, 58, 59, 60, 61, 0
- , 0, 62, 63, 64, 65, 0, 66, 67, 68, 69
- , 70, 222, 103, 9138, 41, 9141, 0, 0, 43, 0
- , 0, 44, 152, 45, 103, 0, 41, 42, 670, 35
- , 0, 0, 0, 35, 0, 0, 672, 326, 0, 0
- , 0, 35, 0, 280, 0, 0, 0, 0, 0, 50
- , 51, 9144, 9147, 9150, 0, 9154, 0, 0, 868, 0
- , 0, 36, 37, 38, 331, 9157, 37, 38, 0, 125
- , 0, 0, 62, 9160, 9163, 9166, 0, 66, 67, 68
- , 69, 70, 0, 0, 71, 0, 9169, 32, 0, 0
- , 0, 9172, 9175, 9178, 42, 103, 40, 9181, 9185, 9188
- , 9191, 9194, 45, 103, 9197, 9200, 9203, 431, 432, 9206
- , 0, 662, 44, 0, 45, 0, 0, 0, 75, 287
- , 0, 0, 0, 0, 50, 51, 9210, 88, 0, 0
- , 9213, 0, 0, 0, 695, 0, 50, 51, 52, 9216
- , 170, 0, 0, 89, 0, 0, 17, 62, 9219, 64
- , 65, 0, 66, 67, 68, 69, 70, 0, 129, 9222
- , 0, 0, 0, 0, 0, 200, 0, 0, 0, 222
- , 0, 0, 0, 0, 0, 0, 152, 394, 0, 0
- , 9225, 0, 0, 0, 0, 0, 0, 0, 152, 186
- , 187, 0, 0, 0, 0, 0, 568, 0, 0, 0
- , 0, 0, 0, 50, 51, 52, 0, 50, 51, 9228
- , 0, 0, 0, 53, 0, 50, 51, 9231, 0, 0
- , 0, 9234, 9237, 57, 58, 59, 9240, 9244, 9247, 9251
- , 62, 9254, 9258, 9261, 69, 9264, 67, 68, 9267, 9271
- , 64, 65, 71, 66, 67, 68, 69, 70, 0, 0
- , 71, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 35, 0, 0, 115, 9274, 117, 375, 0, 0, 0
- , 0, 9277, 120, 121, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 299, 0, 0, 0, 160, 36, 0
- , 38, 0, 36, 37, 38, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 103, 40
- , 9280, 42, 103, 40, 9283, 42, 0, 673, 43, 0
- , 732, 44, 0, 45, 0, 0, 238, 0, 0, 0
- , 0, 0, 0, 35, 0, 90, 97, 0, 0, 9286
- , 299, 35, 0, 91, 92, 0, 0, 0, 0, 0
- , 339, 0, 0, 0, 0, 0, 0, 0, 465, 9289
- , 0, 0, 0, 0, 0, 36, 37, 9292, 0, 467
- , 122, 123, 0, 36, 37, 38, 0, 0, 0, 0
- , 0, 637, 124, 807, 0, 9295, 9298, 656, 0, 0
- , 0, 0, 0, 152, 0, 103, 40, 9301, 42, 0
- , 0, 43, 0, 103, 9305, 41, 9309, 0, 0, 43
- , 0, 9313, 44, 9316, 9319, 697, 0, 0, 0, 103
- , 9323, 9326, 9329, 0, 50, 51, 9332, 103, 0, 41
- , 9335, 299, 0, 446, 0, 0, 0, 0, 0, 228
- , 0, 0, 0, 0, 340, 0, 153, 62, 9338, 64
- , 9341, 69, 9344, 67, 9347, 9350, 9353, 0, 0, 9356
- , 0, 0, 0, 0, 0, 0, 93, 0, 925, 222
- , 0, 477, 0, 0, 289, 0, 290, 395, 0, 0
- , 152, 0, 0, 0, 341, 0, 237, 0, 152, 0
- , 9359, 77, 0, 0, 0, 0, 586, 0, 0, 0
- , 0, 0, 744, 0, 698, 0, 0, 50, 51, 52
- , 0, 0, 738, 9362, 97, 9365, 51, 52, 0, 172
- , 0, 53, 9368, 9371, 9375, 9378, 60, 61, 0, 0
- , 62, 9381, 9384, 9387, 0, 66, 67, 68, 9390, 9393
- , 9398, 9402, 9405, 66, 67, 9408, 69, 9411, 37, 38
- , 71, 0, 0, 0, 0, 0, 0, 0, 520, 781
- , 99, 882, 0, 0, 892, 78, 0, 376, 0, 0
- , 35, 0, 0, 354, 0, 0, 377, 103, 40, 41
- , 42, 0, 9414, 43, 99, 0, 9417, 0, 45, 464
- , 0, 9420, 0, 0, 0, 0, 0, 1379, 699, 466
- , 0, 1379, 9423, 37, 38, 0, 0, 0, 0, 835
- , 0, 468, 1375, 0, 856, 469, 470, 0, 0, 0
- , 1375, 0, 0, 0, 471, 0, 0, 0, 870, 0
- , 0, 702, 9427, 9430, 9434, 9438, 38, 0, 9441, 168
- , 9445, 44, 0, 45, 420, 0, 0, 0, 173, 9448
- , 0, 201, 475, 0, 41, 42, 717, 0, 0, 0
- , 0, 0, 674, 630, 9451, 9454, 41, 42, 0, 0
- , 9458, 9461, 0, 44, 0, 45, 0, 739, 0, 476
- , 169, 170, 0, 0, 0, 0, 0, 0, 0, 9464
- , 51, 9467, 0, 0, 0, 53, 718, 36, 37, 38
- , 0, 0, 0, 0, 0, 0, 222, 0, 0, 0
- , 0, 0, 62, 63, 64, 65, 0, 9470, 67, 68
- , 69, 9474, 37, 38, 71, 0, 0, 427, 40, 428
- , 42, 587, 0, 43, 0, 79, 44, 478, 9477, 0
- , 0, 0, 638, 0, 50, 9480, 52, 0, 0, 152
- , 53, 762, 40, 41, 42, 440, 0, 43, 0, 229
- , 44, 0, 9483, 0, 9487, 51, 9490, 9493, 9497, 64
- , 9500, 0, 66, 67, 68, 69, 9503, 51, 9506, 71
- , 429, 1314, 9509, 294, 0, 0, 17, 0, 0, 0
- , 1016, 56, 57, 58, 9512, 9515, 9518, 296, 0, 62
- , 9521, 9525, 65, 0, 66, 67, 9529, 9532, 9535, 534
- , 483, 9538, 9541, 486, 9545, 9548, 489, 490, 491, 492
- , 493, 494, 495, 9551, 9554, 9557, 613, 0, 0, 0
- , 9561, 0, 0, 0, 9564, 35, 674, 857, 0, 9567
- , 9570, 9573, 769, 9576, 256, 9579, 9582, 9585, 9588, 9592
- , 262, 263, 264, 9595, 9598, 9602, 9605, 59, 9608, 9611
- , 503, 9615, 9619, 9622, 9627, 9630, 0, 9635, 9638, 9643
- , 9648, 70, 469, 470, 71, 0, 95, 9651, 40, 471
- , 299, 0, 1405, 43, 0, 62, 44, 0, 63, 179
- , 0, 64, 45, 0, 472, 616, 0, 66, 719, 0
- , 179, 70, 473, 0, 474, 103, 0, 71, 40, 0
- , 1375, 44, 0, 475, 272, 0, 41, 274, 0, 926
- , 720, 0, 476, 721, 0, 477, 230, 0, 706, 675
- , 0, 36, 152, 0, 38, 237, 0, 431, 169, 0
- , 432, 174, 0, 35, 50, 0, 40, 35, 0, 41
- , 478, 0, 42, 297, 53, 0, 45, 26, 0, 1380
- , 27, 332, 0, 282, 38, 0, 51, 102, 0, 918
- , 52, 0, 928, 62, 0, 53, 65, 0, 1376, 68
- , 0, 50, 36, 70, 0, 51, 37, 0, 52, 38
- , 0, 56, 71, 0, 57, 36, 0, 58, 37, 0
- , 1376, 59, 38, 0, 62, 292, 0, 683, 65, 343
- , 103, 0, 66, 41, 0, 67, 31, 42, 0, 68
- , 32, 0, 69, 96, 0, 70, 43, 0, 71, 44
- , 0, 103, 284, 0, 40, 285, 0, 41, 286, 220
- , 0, 103, 175, 80, 0, 1376, 40, 0, 41, 43
- , 0, 846, 44, 0, 479, 43, 0, 480, 44, 378
- , 0, 481, 663, 0, 389, 482, 283, 664, 45, 0
- , 483, 284, 0, 484, 285, 0, 485, 286, 0, 486
- , 753, 293, 0, 490, 250, 0, 491, 14, 0, 492
- , 15, 0, 106, 493, 617, 0, 494, 636, 0, 498
- , 808, 0, 500, 294, 0, 50, 588, 252, 0, 51
- , 296, 0, 429, 254, 0, 105, 181, 0, 503, 189
- , 0, 106, 190, 0, 63, 344, 0, 64, 222, 0
- , 179, 66, 107, 0, 70, 152, 0, 797, 422, 53
- , 257, 0, 798, 315, 260, 0, 287, 316, 262, 0
- , 35, 263, 0, 618, 56, 266, 0, 50, 57, 267
- , 0, 51, 58, 0, 52, 59, 0, 50, 61, 0
- , 52, 53, 268, 0, 62, 269, 0, 442, 63, 270
- , 0, 53, 65, 0, 56, 69, 0, 57, 70, 0
- , 59, 574, 0, 56, 60, 71, 0, 57, 61, 0
- , 60, 62, 0, 61, 63, 0, 180, 62, 0, 36
- , 63, 66, 81, 0, 37, 64, 67, 0, 38, 65
- , 68, 97, 0, 66, 70, 0, 69, 71, 0, 747
- , 45, 0, 783, 422, 0, 929, 883, 0, 722, 422
- , 0, 41, 639, 0, 42, 26, 0, 52, 423, 0
- , 809, 38, 237, 0, 37, 31, 0, 250, 38, 32
- , 0, 62, 40, 0, 63, 41, 0, 64, 42, 283
- , 0, 65, 284, 0, 66, 43, 286, 0, 69, 44
- , 0, 125, 70, 0, 667, 103, 0, 40, 1353, 0
- , 668, 41, 0, 41, 43, 0, 128, 113, 0, 35
- , 1353, 0, 317, 1353, 0, 37, 1353, 0, 152, 1353
- , 0, 641, 1024, 0, 727, 119, 0, 152, 121, 0
- , 734, 152, 0, 373, 40, 50, 0, 41, 51, 0
- , 42, 52, 0, 422, 53, 0, 50, 5, 0, 51
- , 6, 0, 52, 7, 0, 51, 8, 0, 52, 53
- , 0, 746, 443, 63, 0, 873, 53, 65, 0, 799
- , 66, 0, 67, 99, 0, 65, 73, 0, 63, 66
- , 74, 0, 64, 67, 0, 65, 68, 160, 0, 66
- , 70, 0, 69, 71, 0, 204, 445, 0, 784, 422
- , 38, 0, 50, 770, 0, 51, 771, 0, 53, 9
- , 0, 677, 103, 0, 885, 64, 0, 69, 35, 0
- , 424, 168, 0, 401, 288, 0, 283, 669, 0, 41
- , 152, 0, 43, 130, 0, 176, 52, 0, 591, 53
- , 0, 547, 154, 0, 548, 65, 0, 125, 70, 0
- , 576, 126, 0, 125, 152, 127, 0, 643, 52, 0
- , 687, 447, 0, 939, 68, 0, 209, 70, 0, 592
- , 579, 363, 0, 837, 578, 581, 0, 579, 97, 0
- , 1047, 451, 0, 1047, 35, 0, 1047, 723, 0, 1047
- , 36, 0, 1296, 37, 0, 517, 41, 0, 242, 45
- , 0, 103, 319, 0, 785, 40, 0, 37, 203, 0
- , 36, 646, 0, 373, 40, 0, 773, 103, 0, 41
- , 106, 43, 0, 44, 50, 0, 43, 51, 0, 45
- , 52, 0, 45, 53, 0, 800, 536, 131, 0, 50
- , 380, 63, 0, 51, 64, 0, 894, 52, 65, 0
- , 108, 67, 0, 401, 53, 17, 68, 0, 109, 69
- , 0, 111, 71, 0, 57, 179, 0, 60, 370, 0
- , 786, 736, 62, 0, 594, 63, 0, 64, 537, 0
- , 201, 193, 0, 886, 538, 0, 628, 83, 0, 792
- , 1411, 0, 180, 1411, 0, 50, 369, 0, 812, 50
- , 0, 52, 53, 0, 56, 370, 0, 60, 62, 0
- , 61, 63, 0, 63, 66, 0, 64, 67, 0, 65
- , 68, 0, 66, 70, 0, 69, 71, 0, 35, 132
- , 0, 83, 1221, 0, 36, 133, 0, 38, 103, 0
- , 40, 44, 0, 42, 45, 241, 0, 45, 647, 0
- , 204, 1047, 0, 709, 1047, 0, 152, 1047, 0, 194
- , 1047, 0, 222, 1341, 0, 152, 51, 0, 50, 5
- , 0, 51, 11, 0, 52, 7, 0, 14, 62, 0
- , 15, 63, 0, 64, 8, 0, 895, 53, 65, 0
- , 50, 66, 0, 51, 67, 0, 52, 68, 0, 941
- , 56, 71, 0, 787, 59, 0, 60, 16, 0, 56
- , 62, 0, 57, 63, 0, 58, 64, 0, 59, 65
- , 0, 61, 66, 207, 0, 62, 69, 0, 63, 70
- , 0, 64, 253, 0, 179, 66, 0, 67, 181, 0
- , 68, 299, 0, 373, 595, 0, 910, 596, 279, 0
- , 848, 679, 0, 388, 38, 0, 452, 242, 0, 724
- , 351, 0, 639, 458, 0, 209, 36, 0, 179, 41
- , 152, 43, 0, 42, 101, 0, 35, 381, 50, 0
- , 597, 52, 0, 648, 53, 0, 320, 63, 0, 477
- , 69, 0, 36, 70, 0, 519, 37, 0, 99, 31
- , 0, 32, 352, 0, 106, 195, 0, 42, 302, 0
- , 43, 107, 0, 44, 35, 0, 35, 50, 209, 0
- , 52, 210, 0, 690, 53, 0, 36, 61, 0, 65
- , 211, 0, 737, 68, 0, 36, 47, 70, 0, 826
- , 37, 0, 237, 103, 0, 48, 42, 0, 238, 43
- , 0, 41, 49, 0, 54, 426, 0, 57, 156, 0
- , 942, 59, 0, 50, 36, 136, 0, 51, 37, 0
- , 52, 38, 0, 1379, 333, 0, 50, 1118, 63, 0
- , 51, 1118, 64, 0, 52, 1118, 65, 0, 1118, 66
- , 0, 468, 67, 0, 1375, 68, 0, 62, 71, 0
- , 896, 63, 0, 1375, 65, 0, 471, 68, 39, 0
- , 69, 40, 0, 1118, 70, 41, 0, 472, 44, 0
- , 598, 212, 0, 373, 244, 0, 402, 476, 0, 943
- , 303, 0, 478, 51, 0, 36, 63, 0, 37, 64
- , 0, 38, 65, 0, 50, 66, 0, 51, 67, 0
- , 52, 68, 0, 167, 70, 0, 410, 40, 0, 482
- , 382, 0, 483, 103, 0, 485, 41, 0, 486, 42
- , 0, 491, 14, 0, 492, 15, 0, 413, 493, 0
- , 498, 197, 0, 500, 16, 0, 944, 18, 0, 467
- , 158, 0, 502, 159, 0, 504, 160, 0, 152, 72
- , 0, 922, 696, 103, 169, 0, 40, 170, 0, 41
- , 19, 0, 42, 20, 0, 35, 50, 21, 0, 43
- , 51, 0, 643, 52, 22, 0, 45, 53, 0, 36
- , 70, 0, 41, 23, 0, 42, 24, 0, 222, 397
- , 0, 44, 35, 0, 802, 45, 0, 52, 750, 0
- , 36, 63, 0, 37, 64, 0, 38, 65, 103, 0
- , 66, 41, 353, 0, 67, 222, 42, 0, 70, 43
- , 0, 71, 44, 0, 622, 45, 355, 25, 0, 40
- , 82, 0, 699, 35, 324, 0, 862, 45, 0, 701
- , 51, 0, 61, 162, 0, 36, 63, 0, 37, 64
- , 0, 38, 65, 0, 703, 103, 0, 705, 41, 106
- , 0, 41, 390, 0, 44, 35, 0, 674, 51, 0
- , 850, 52, 0, 933, 682, 0, 36, 63, 0, 542
- , 37, 64, 0, 38, 65, 0, 50, 66, 33, 0
- , 51, 67, 0, 52, 68, 0, 53, 78, 0, 62
- , 40, 0, 63, 179, 428, 0, 64, 42, 0, 65
- , 103, 0, 40, 138, 0, 66, 41, 462, 43, 0
- , 67, 48, 42, 0, 69, 44, 0, 70, 43, 0
- , 71, 44, 0, 607, 52, 0, 897, 429, 0, 54
- , 531, 0, 718, 56, 0, 67, 222, 0, 68, 237
- , 0, 71, 651, 35, 0, 152, 365, 0, 623, 524
- , 50, 36, 0, 51, 37, 0, 758, 52, 38, 0
- , 51, 102, 0, 52, 53, 0, 57, 36, 0, 58
- , 37, 0, 59, 38, 0, 56, 60, 178, 0, 57
- , 61, 0, 60, 62, 0, 61, 63, 0, 63, 66
- , 0, 64, 67, 0, 65, 68, 383, 103, 0, 69
- , 40, 0, 66, 70, 41, 0, 67, 42, 0, 69
- , 71, 0, 70, 43, 0, 71, 44, 0, 179, 41
- , 0, 42, 198, 0, 543, 391, 0, 430, 357, 107
- , 0, 179, 433, 152, 0, 934, 180, 109, 0, 751
- , 56, 0, 50, 57, 0, 51, 58, 0, 52, 59
- , 0, 790, 53, 0, 652, 62, 0, 238, 63, 0
- , 513, 66, 0, 56, 69, 0, 57, 70, 0, 60
- , 71, 0, 68, 305, 0, 477, 69, 0, 887, 169
- , 0, 36, 139, 0, 77, 245, 0, 160, 728, 0
- , 817, 49, 0, 878, 50, 0, 545, 52, 0, 818
- , 57, 0, 819, 58, 0, 35, 63, 0, 544, 70
- , 0, 37, 791, 778, 0, 841, 384, 0, 664, 888
- , 0, 697, 79, 0, 68, 605, 0, 69, 35, 0
- , 666, 820, 0, 401, 65, 0, 828, 1379, 0, 699
- , 467, 0, 701, 468, 0, 853, 1375, 0, 1375, 143
- , 0, 318, 471, 0, 843, 248, 0, 779, 246, 0
- , 703, 475, 247, 0, 705, 41, 385, 0, 476, 53
- , 0, 477, 56, 0, 392, 59, 0, 35, 36, 0
- , 924, 402, 145, 0, 901, 403, 0, 822, 36, 41
- , 0, 37, 42, 0, 38, 146, 0, 479, 43, 0
- , 480, 44, 147, 0, 550, 481, 0, 482, 45, 0
- , 625, 483, 0, 485, 72, 0, 520, 488, 0, 866
- , 99, 490, 400, 0, 125, 493, 0, 552, 494, 0
- , 496, 325, 0, 498, 401, 0, 40, 361, 0, 823
- , 328, 0, 947, 222, 0, 238, 362, 0, 36, 763
- , 152, 0, 38, 363, 0, 36, 43, 0, 557, 97
- , 0, 558, 776, 0, 560, 222, 0, 561, 777, 0
- , 562, 831, 0, 563, 50, 0, 564, 51, 0, 83
- , 52, 0, 41, 152, 0, 565, 42, 402, 53, 0
- , 566, 40, 0, 413, 41, 43, 403, 0, 533, 223
- , 0, 45, 548, 505, 0, 914, 65, 0, 35, 50
- , 70, 148, 0, 51, 549, 0, 57, 125, 0, 58
- , 552, 0, 59, 248, 0, 61, 183, 0, 780, 64
- , 0, 634, 35, 0, 67, 99, 0, 36, 70, 0
- , 71, 373, 0, 712, 185, 0, 152, 37, 0, 42
- , 889, 0, 44, 35, 0, 50, 655, 0, 52, 656
- , 0, 52, 53, 39, 0, 554, 42, 0, 53, 165
- , 0, 555, 43, 0, 558, 44, 0, 560, 45, 0
- , 38, 562, 0, 62, 563, 0, 63, 564, 0, 65
- , 237, 0, 63, 66, 0, 64, 67, 565, 0, 65
- , 68, 0, 69, 566, 436, 35, 0, 66, 70, 413
- , 127, 0, 69, 71, 0, 373, 224, 0, 902, 103
- , 0, 389, 42, 0, 43, 404, 0, 44, 35, 47
- , 0, 106, 37, 0, 36, 408, 0, 50, 36, 49
- , 0, 51, 37, 0, 52, 38, 103, 0, 65, 103
- , 0, 40, 606, 50, 0, 66, 41, 127, 51, 0
- , 67, 42, 168, 52, 0, 68, 103, 0, 69, 40
- , 35, 0, 70, 41, 43, 0, 222, 42, 53, 0
- , 71, 44, 0, 45, 607, 0, 44, 170, 54, 0
- , 152, 58, 0, 608, 59, 0, 527, 61, 0, 386
- , 64, 0, 57, 152, 0, 59, 364, 0, 62, 40
- , 0, 63, 413, 41, 0, 64, 42, 0, 915, 65
- , 0, 179, 66, 43, 0, 67, 804, 657, 366, 0
- , 69, 44, 0, 222, 45, 0, 635, 367, 0, 152
- , 51, 0, 583, 52, 0, 636, 53, 0, 832, 62
- , 0, 50, 63, 0, 51, 64, 0, 903, 52, 65
- , 0, 50, 179, 66, 0, 51, 67, 0, 52, 53
- , 68, 0, 180, 56, 0, 60, 62, 0, 61, 63
- , 0, 63, 179, 66, 72, 0, 64, 67, 389, 0
- , 65, 68, 0, 66, 70, 0, 69, 71, 0, 160
- , 185, 0, 741, 52, 0, 713, 180, 0, 845, 38
- , 0, 180, 1047, 0, 1047, 62, 0, 415, 63, 0
- , 1047, 64, 0, 1047, 66, 0, 833, 68, 0, 1047
- , 103, 0, 125, 43, 0, 437, 414, 0, 103, 1047
- , 0, 40, 35, 1047, 0, 41, 1047, 0, 44, 36
- , 0, 45, 422, 38, 0, 714, 38, 0, 730, 103
- , 0, 152, 43, 0, 670, 169, 0, 671, 103, 0
- , 44, 50, 0, 201, 45, 52, 0, 674, 127, 114
- , 0, 916, 805, 234, 0, 890, 51, 222, 0, 62
- , 118, 0, 64, 658, 368, 0, 65, 119, 0, 66
- , 121, 0, 67, 855, 0, 68, 171, 0, 69, 436
- , 0, 70, 794, 127, 0, 35, 50, 0, 584, 52
- , 0, 128, 226, 0, 62, 150, 0, 50, 63, 0
- , 51, 64, 0, 52, 65, 0, 53, 17, 68, 0
- , 36, 70, 0, 37, 151, 0, 65, 160, 0, 71
- , 609, 0, 42, 387, 0, 43, 336, 0, 44, 35
- , 0, 1049, 255, 0, 264, 122, 0, 265, 123, 0
- , 767, 267, 0, 38, 268, 0, 731, 74, 0, 40
- , 126, 0, 125, 41, 127, 0, 222, 42, 0, 1049
- , 45, 0, 1049, 271, 0, 1049, 272, 0, 1049, 273
- , 0, 1049, 274, 0, 1049, 275, 0, 1049, 276, 0
- , 1049, 279, 0, 53, 38, 0, 938, 57, 0, 71
- , 40, 0, 659, 42, 0, 52, 26, 0, 337, 27
- , 0, 417, 338, 281, 0, 53, 282, 0, 742, 36
- , 0, 36, 63, 0, 37, 64, 0, 38, 65, 0
- , 31, 222, 0, 904, 103, 0, 40, 126, 0, 41
- , 127, 0, 41, 152, 43, 0, 42, 283, 0, 284
- , 128, 0, 285, 44, 0, 43, 286, 0, 40, 44
- , 0, 507, 41, 0, 42, 45, 0, 433, 418, 43
- , 0, 585, 52, 0, 168, 53, 0, 169, 227, 0
- , 312, 63, 0, 654, 71, 0, 891, 152, 0, 52
- , 53, 0, 806, 52, 0, 795, 53, 0, 113, 56
- , 0, 715, 60, 62, 0, 61, 63, 0, 948, 114
- , 64, 0, 664, 65, 0, 439, 63, 66, 0, 64
- , 67, 0, 65, 68, 0, 66, 70, 0, 62, 69
- , 71, 0, 63, 70, 0, 522, 116, 0, 160, 119
- , 0, 415, 41, 0, 41, 43, 0, 419, 288, 0
- , 869, 768, 0, 401, 38, 0, 467, 743, 0, 660
- , 222, 0, 179, 41, 152, 0, 520, 40, 44, 0
- , 99, 42, 45, 0, 696, 103, 0, 179, 41, 0
- , 626, 42, 45, 0, 834, 50, 0, 41, 51, 0
- , 42, 52, 0, 52, 53, 0, 42, 53, 0, 313
- , 63, 0, 65, 68, 0, 66, 70, 0, 949, 68
- , 0, 477, 69, 0, 881, 70, 0, 71, 76, 0
- , 97, 188, 0, 569, 53, 0, 35, 50, 0, 185
- , 56, 0, 716, 50, 57, 0, 51, 58, 0, 52
- , 59, 0, 50, 63, 0, 51, 64, 0, 52, 65
- , 0, 62, 69, 0, 50, 770, 63, 70, 0, 51
- , 570, 64, 0, 52, 65, 0, 571, 71, 0, 68
- , 78, 0, 36, 70, 0, 520, 699, 0, 700, 44
- , 0, 701, 465, 0, 35, 467, 36, 0, 703, 103
- , 0, 704, 472, 40, 0, 36, 705, 41, 0, 37
- , 42, 0, 179, 473, 43, 0, 474, 237, 0, 905
- , 1375, 0, 237, 103, 0, 40, 631, 35, 0, 43
- , 291, 0, 168, 661, 0, 35, 50, 0, 52, 94
- , 0, 594, 66, 152, 0, 36, 70, 0, 222, 45
- , 0, 639, 51, 0, 45, 782, 508, 0, 50, 342
- , 0, 52, 250, 0, 652, 14, 62, 0, 15, 63
- , 0, 906, 65, 0, 50, 70, 0, 52, 745, 0
- , 53, 250, 0, 59, 248, 0, 60, 572, 0, 61
- , 252, 0, 238, 63, 254, 0, 64, 222, 181, 0
- , 68, 160, 0, 69, 611, 0, 70, 612, 0, 71
- , 484, 0, 179, 485, 152, 0, 97, 487, 0, 488
- , 35, 0, 436, 496, 0, 127, 497, 0, 201, 498
- , 573, 0, 1016, 128, 0, 1314, 500, 0, 631, 50
- , 0, 501, 51, 0, 796, 52, 0, 255, 235, 0
- , 53, 257, 0, 464, 258, 0, 259, 36, 0, 465
- , 260, 37, 0, 261, 38, 0, 614, 265, 0, 1379
- , 56, 266, 0, 57, 267, 0, 466, 58, 0, 1379
- , 60, 0, 467, 502, 61, 0, 615, 504, 268, 0
- , 62, 269, 0, 50, 1405, 63, 270, 0, 51, 64
- , 0, 52, 1405, 65, 78, 0, 36, 66, 0, 917
- , 468, 37, 67, 0, 53, 1375, 38, 68, 0, 180
- , 69, 0, 1375, 103, 0) ;
- --| Actions to perform for all combinations of parser
- --| states and input tokens.
- -- NYU Reference Name: ACTION_TABLE1
-
- ActionTableTwo :
- constant array (ActionTableTwoRange)
- of GC.ParserInteger :=
- (71747,71748, 0,165573, 0,165575,115905, 0, 0, 0
- ,259403, 0, 0,259406,259407,259408, 0, 0, 0, 0
- ,182147,182148, 0, 0,182151, 0, 0, 0, 0,182156
- , 0,121449, 0,248388, 0, 0, 0,204240, 0, 0
- , 0, 0, 0, 0, 0, 0, 0,209769, 0, 0
- , 0,264963, 0, 0, 0, 0, 0, 0, 0, 0
- , 0,110441, 0,259456, 0, 0, 0, 0, 0,176677
- , 0, 0,71819, 0,292581, 0, 0, 0, 0, 0
- ,27675, 0, 0, 0,264996, 0, 0,127024,265000, 0
- , 0,127028,182219, 0,60803, 0, 0, 0, 0, 0
- , 0, 0, 0,182230,132560, 0, 0, 0, 0, 0
- , 0,71858,71859,265025, 0, 0, 0, 0, 0,265031
- , 0, 0,265034, 0, 0, 0,60835,60836, 0,193294
- ,182257, 0, 0, 0,71881,71882, 0, 0,71885,71886
- , 0,71888, 0, 0, 0, 0, 0, 0, 0,182276
- ,182277, 0, 0, 0,182281,182282, 0,60866, 0, 0
- , 0, 0, 0, 0, 0, 0, 0,60876, 0, 0
- , 0,121589, 0, 0, 0,149188, 0, 0, 0,171268
- , 0, 0, 0,149196, 0, 0, 0, 0, 0, 0
- , 0, 0,248547,248548,248549, 0, 0, 0, 0, 0
- ,248555,248556,248557, 0,248559, 0, 0,259600, 0,60918
- ,265122, 0, 0, 0,55404,55405, 0,121635,248573, 0
- , 0, 0, 0, 0, 0, 0, 0,265139, 0, 0
- , 0,265143, 0, 0, 0,55425, 0,248592, 0,248594
- , 0, 0, 0, 0, 0, 0,149259, 0,265160, 0
- , 0,265163, 0, 0,265166,265167,265168, 0, 0, 0
- ,265172,171350, 0, 0, 0,187911, 0, 0,60977,60978
- ,60979, 0,55462,55463, 0,55465,55466, 0,55468, 0
- , 0,55471,55472, 0, 0, 0, 0,60996, 0,171378
- , 0, 0, 0,61002, 0, 0,61005,61006,61007, 0
- , 0,149314, 0, 0, 0,171394,171395, 0, 0,149322
- ,149323, 0, 0, 0, 0,149328, 0,171406,171407, 0
- ,171409, 0,94145,171412, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0,55528,55529
- ,55530, 0,204545,204546,204547,204548, 0,44499,204551, 0
- ,138325,204554, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 363, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0,270805, 0, 0, 0, 0, 0
- , 0, 0,50053, 0,50055, 0, 0, 0, 0,182516
- , 0, 0, 0, 0, 0,204598, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0,61123, 0,204619,177025, 418,171508
- ,177028, 0, 0,132879,55614, 0, 0,204630, 0,243265
- ,149443, 0, 0,55623,171523, 0,55626, 0, 0, 0
- , 0, 0, 0, 0, 0, 0,61155,61156,61157, 0
- , 0, 0, 0, 0,204657,204658, 0, 0, 0, 0
- ,204663, 0,149475,149476, 0,188111,171555, 0, 0,204672
- ,204673,204674,204675,204676,204677, 0,61185, 0, 0, 0
- , 0,55671, 0,204686,204687, 0, 0,61196, 0,204692
- , 0, 0, 0, 0, 0,149508,171585,171586, 0,171588
- ,55690,149514,171591,149516, 0,171594, 0,171596, 0,215750
- ,215751,55701,94335, 0,243350, 0, 0, 0, 0,160570
- , 0, 0,33636, 0,77790, 0, 0, 0,193693, 0
- , 0,282000, 0, 0, 0, 0, 0, 0, 0, 0
- , 0,243377,243378,243379, 0,188191, 0,11585, 0, 0
- , 0, 0, 0, 0, 0, 0, 0,232355, 0,232357
- , 0, 0, 0, 0, 0, 0,149579,33681,33682,33683
- , 0,33685,33686, 0, 0, 0,33690, 0, 0, 0
- , 0, 0,122000,204786,204787,204788, 0,232385, 0, 0
- , 0,287579, 0,232391, 0, 0,232394, 0,232396, 0
- , 0, 0, 0, 603, 0, 0, 0, 0,171697, 0
- , 0,61320, 0,61322, 0,11653, 0, 0,61327,61328
- ,61329, 0,144116,61332, 0, 0, 0,149640,149641,149642
- , 0,171720, 0, 0, 0,149648, 0,171726,171727, 0
- ,171729, 0, 0,171732, 0, 0, 0,22723, 0, 0
- , 0, 0,116551, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0,232470, 0,271105, 0, 0, 0, 0,22755
- ,22756, 0, 0,50354,33798,33799, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0,33810,11735, 0, 0
- , 0,232499, 0, 0, 0, 0, 0, 0, 0, 0
- ,22786,22787,22788, 0, 0,22791, 0, 0, 0, 0
- , 0, 0,232520,232521, 0,232523, 0,232525,232526,232527
- , 0,232529, 0, 0,232532, 0,105597, 0, 0, 739
- , 0,94564,271173, 0,271175, 0, 0, 0, 0, 0
- , 0, 0, 0,238070,238071,238072, 0, 0, 0, 0
- ,171849, 0,39395,39396,39397, 0, 0, 0, 0, 0
- , 0,193936,193937, 0, 0, 0,287764,287765, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0,133245
- , 0, 0,39425,39426, 0,39428, 0, 0, 0, 0
- , 0,39434,193967,39436, 0, 0, 0, 0,149821, 0
- ,260203, 0,149825, 0, 0, 0, 0, 0, 0, 0
- ,193985,22897,22898, 0,271255,50496,193991, 0, 0, 0
- , 0,127768, 0, 0,238151, 0,282305, 0, 0,216080
- , 0, 0,144336,144337, 0,22921, 0, 0, 0,22925
- ,22926,22927,22928, 0, 0, 0, 0, 0, 0,127796
- , 0, 0, 0, 0, 0, 0,39499, 0,260261, 0
- , 0, 0, 0,144367, 0,56065, 0, 0, 0,78145
- ,39513, 0, 0,33997, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0,276844, 0, 0,144391, 0, 0
- , 0,166471, 0, 0,39537,39538, 0, 0, 0,116808
- ,39543, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0,221682, 0,116823, 0, 0,39560,39561,39562
- ,39563, 0,39565,39566, 0,39568, 0, 0,194103,39572
- , 0, 0,34056, 0,249299, 0, 0,78213, 0,78215
- ,28545, 0, 0, 0,50625, 0,94779, 0, 0, 0
- ,144454, 0, 0,144457, 0, 0, 0,166537,166538,144463
- , 0,144465, 0,166543, 0,166545, 0, 0,183105, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0,111371, 0, 0, 0, 0, 0,205200, 0, 0
- , 0, 0, 0, 0, 0,293512, 0, 0, 0, 0
- , 0,243847, 0,293520, 0, 0,116915, 0,116917,282488
- , 0, 0, 0, 0,288012, 0, 0, 0, 0,78295
- , 0, 0,238349, 0, 0, 0,116935, 0,243874, 0
- ,243876, 0, 0,243879, 0, 0, 0, 0, 0, 0
- ,39683,243887, 0,243889, 0, 0, 1056, 0,56248, 0
- , 0, 0, 0, 0,172153,172154, 0, 0,243904, 0
- , 0, 0, 0,243909, 0,243911, 0,243913,243914,243915
- ,243916,243917, 0, 0,39717,243921,243922,243923, 0, 0
- ,243926,243927, 0,243929,243930,243931, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0,172195,172196,172197, 0
- , 0,172200,39745,39746, 0,39748,117015, 0,39751, 0
- , 0,39754, 0, 0, 0, 0, 0, 0,183255, 0
- ,260523,282600,150145, 0, 0,61844, 0, 0,172227,172228
- ,28735, 0,172231, 0, 0,172234, 0,172236,238465, 0
- , 0, 0, 0,166723, 0, 0,282625,188803, 0,216400
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0,56371, 0, 0, 0,166755, 0,166757,260581, 0
- ,188836,188837, 0, 0, 0, 0, 0,39830, 0, 0
- , 0,56391, 0, 0,255078, 0, 0, 0, 0, 0
- ,172299, 0, 0, 0, 0,166785, 0,166787,166788, 0
- ,188866, 0,188868, 0, 0, 0, 0, 0,188874, 0
- , 0, 0, 0,172322, 0,50906, 0,233035,210960, 0
- , 0, 0, 0, 0, 0, 0,299272,39880, 0, 0
- , 0, 0,39885, 0, 0, 0,39889,172346, 0, 0
- , 0, 0, 0,172352, 0,172354,172355, 0,172357, 0
- , 0, 0, 0, 0,172363, 0,172365,172366,172367,172368
- ,172369, 0,150295,172372, 0, 0, 0, 0, 0, 0
- , 0, 0, 0,188939, 0, 0, 0, 0, 0, 0
- ,166870,166871, 0,166873,188950, 0, 0, 1307, 0, 0
- , 0,111691, 0, 0, 0, 0, 0, 0, 0,271750
- ,271751, 0, 0, 1323, 0, 1325,271757, 0,166898,166899
- , 0, 0,188978, 0, 1334, 0, 0,188983, 0, 0
- , 0, 0, 0, 1343, 0, 0, 0,188993,188994,188995
- , 0, 0,166922,166923,189000, 0, 0, 0,166928, 0
- ,189006,189007, 0,189009, 0, 0,189012, 0, 0, 0
- , 0, 0, 0, 0,133830,133831, 0, 0, 0, 0
- , 0,133837, 0, 0, 0,282854,266298, 0, 0, 0
- ,150403,78657, 0,200077, 0, 0,244232,189043,194563, 0
- , 0, 0, 0,40036,40037, 0, 0, 0,139383, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0,150435,150436,150437, 0, 0,17984, 0, 0
- ,194595,194596, 0,40066,40067,40068, 0, 0,40071, 0
- , 0,40074, 0,40076, 0, 0, 0, 0,128385,12487
- , 0, 0,150465,150466,150467,150468, 0, 0,150471, 0
- ,194625, 0,194627, 0, 0, 0,194631, 0, 0,194634
- , 0, 0,12510, 0, 0, 0,12514, 0,12516,216720
- ,78746,12519, 0, 0, 0, 0, 0, 0, 0,12527
- , 0,12529, 0, 0, 0, 0,78762,128434, 0,78765
- , 0, 0, 0, 0, 0,150518, 0, 0,167078, 0
- ,78776,12549,12550, 0,12552,12553,12554, 0, 0,12557
- ,12558, 0, 0,12561,12562,12563, 0,12565,12566,12567
- , 0,12569,12570,12571,194699, 0, 0,150550, 0, 0
- , 0, 0, 0, 0,40177, 0,40179, 0, 0, 0
- ,40183,255425, 0,255427,255428, 0, 0, 0,238875, 0
- , 0,139536,139537, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0,40208,40209, 0,194743, 0
- ,150593,150594, 0, 0,150597, 0,117485, 0, 0, 0
- , 0,194756, 0,150606,150607, 0, 0, 0,194763,150612
- , 0, 0, 0,194768,194769,56795, 0,194772, 0, 0
- ,139585,45763, 0, 0,56804, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0,78892, 0,78894,78895
- , 0, 0, 0, 0, 0, 0,255510, 0, 0,128576
- , 0, 0, 0,45795,45796, 0, 0,89951, 0,117548
- ,117549,117550, 0,117552, 0, 0, 0, 0,205861, 0
- , 0, 0, 0,255537,255538,255539, 0, 0, 0, 0
- , 0, 1671, 0,45825,45826,45827,45828,266589, 0,45831
- , 1680, 0, 0, 0,67912, 0, 0, 0, 0, 0
- ,18247, 0, 0, 0,62403, 0, 0, 0, 0, 0
- , 0, 0, 0,40336,40337, 0, 0,117606, 0, 0
- , 0, 0,117611,117612,117613,117614,117615,117616,78984, 0
- , 0, 0, 0, 0, 0, 0, 0,62436,62437, 0
- , 0,62440, 0, 0,40367, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0,40385, 0, 0, 0,62465,62466, 0, 0
- , 0, 0,62471, 0, 0,62474,239083,62476,128705, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0,250136, 0, 0, 0, 0,45938, 0, 0, 0
- , 0, 0,261185, 0, 0,117694,217037, 0, 0,217040
- , 0, 0, 0,117702,117703,117704, 0,117706, 0, 0
- ,45962,45963, 0,45965,45966,45967, 0, 0, 0,123237
- , 0, 0, 0, 0,239141, 0, 0, 0, 0, 0
- ,62539, 0, 0, 0, 0, 0,128773, 0, 0, 0
- ,250195, 0, 0, 0, 0,57035, 0,123265,123266,123267
- , 0, 0, 0, 0, 0,189501, 0, 0,123276, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0,62578
- , 0,189517, 0, 0, 0,277825,29471,62586, 0,62588
- , 0, 0,123300,62592,62593,62594,62595,62596, 0,73636
- ,73637,62600,62601,62602, 0, 0,62605,62606, 0,62608
- , 0, 0,139877,62612,117803, 0,250261, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0,73666
- ,73667, 0, 0, 0, 0, 0, 0,73674,51599,73676
- ,139905,139906, 0,139908, 0, 0,139911, 0, 0,139914
- , 0,139916,206145, 0,206147,206148, 0, 0, 0, 0
- , 0,35065, 0,184080, 0,24031, 0, 0, 0,123377
- ,123378,123379,117861, 0, 0,123383, 0, 0, 0, 0
- , 0, 0,123390, 0,123392, 0,123394, 0,123396,123397
- , 0, 0,123400,123401,123402,123403, 0,123405,123406,123407
- ,123408,123409,73739, 0,123412,24071, 0, 0, 0, 0
- , 0, 0, 0,73750,139979, 0, 0, 0, 0, 0
- ,40643,266923, 0, 0, 0,139990,90320, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0,206230, 0, 0
- ,73777,73778,73779, 0, 0, 0,73783,195202, 0,195204
- ,222800, 0, 0, 0, 0, 0, 0,195212,140023,195214
- ,195215, 0, 0,73800, 0, 0, 0, 0, 0, 0
- , 0,73808,73809,195228,195229, 0, 0,140042, 0,266981
- ,140045,140046, 0, 0, 0,40708, 0,140052,40711, 0
- , 0, 0, 0,40716, 0, 0,195251, 0,195253, 0
- , 0, 0,151105, 0,129031, 0,195261,195262,123516, 0
- ,195265, 0,195267,195268, 0, 0, 0, 0,173197, 0
- , 0,173200,294619,162164, 0, 0, 0, 0, 0, 0
- , 0,162172, 0, 0, 0,40758,261519, 0, 0, 0
- ,233928, 0, 0, 0, 0, 0, 0, 0,233936,233937
- , 0, 0, 0, 0, 0,283614,40779, 0, 0, 0
- , 0, 0, 0, 0,233952, 0, 0,40790, 0, 0
- , 0, 0, 0, 0, 0, 0,233964, 0, 0,233967
- , 0, 0,129109, 0, 0, 0,73923,123595, 0, 0
- ,245016, 0,123600,245019,40817, 0,40819, 0, 0,57379
- ,40823,189837,206395,233991,189840,300221,40829,40830,211920,40832
- ,40833,40834,40835,40836,40837, 0, 0,40840, 0, 0
- , 0, 0, 0, 0, 0,40848, 0, 0, 0,40852
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0,118134, 0, 0,73985, 0
- ,73987,73988,151255, 0,73991, 0, 0,73994, 0,73996
- ,140225,234049,195417,234051, 0,195420,195421, 0, 0,195424
- , 0, 0,195427,195428,195429,195430, 0, 0, 0,195434
- ,195435,195436,195437, 0,195439, 0, 0, 0, 0, 0
- , 0, 0, 0,223043, 0, 2285, 0, 0,195453, 0
- , 0, 0,267204,294800, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0,195473, 0
- , 0, 0,74059, 0, 0,223075,223076,223077, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0,40966, 0, 0,118235, 0, 0, 0
- , 0, 0, 0,184470, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0,223114, 0, 0, 0,24434, 0
- , 0, 0, 0, 0, 0,74112, 0, 0, 0, 0
- ,184497,184498,184499,74120,74121,74122,74123, 0,74125,74126
- ,74127,74128, 0,151396,151397,74132, 0,18944, 0, 0
- , 0, 0,41025, 0,41027,41028, 0, 0,223158, 0
- ,140375, 0, 0, 0, 0, 0,63115, 0, 0, 0
- ,107271, 0,151425,151426, 0, 0,107277,228696,151431, 0
- ,228699, 0, 0, 0,201108, 0, 0,151440, 0, 0
- ,223190,173520,118331, 0, 0, 0, 0,129374, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0,256323
- , 0,283920, 0,101795,101796,101797, 0,223217,223218, 0
- , 0, 0, 0,223223, 0,151478, 0, 0, 0, 0
- , 0, 0,223232,223233,223234,223235,223236,223237, 0, 0
- ,223240, 0, 0, 0,101826, 0, 0,223247,223248, 0
- , 0,79757, 0, 0, 0, 0, 0,151510, 0, 0
- , 0, 0, 2502, 2503, 2504, 0, 0,41140, 0, 0
- ,206713,256385, 0,256387,256388,278465, 0,256391,239835, 0
- ,256394, 0, 0,223283,151537, 0,151539, 2527, 2528, 0
- ,151543, 0, 0, 0, 0, 0, 0, 2537, 2538,151552
- ,151553,151554,151555,151556, 0, 0, 0,151560, 0, 0
- , 0, 0,151565,151566,151567,151568,151569,101899, 0,151572
- , 0, 8080,96385, 0, 0,267477, 0,267479, 0,118468
- ,140545, 0, 0, 0,162625, 0, 0, 0,184705,184706
- , 0,184708, 0,112963,184711,256459,228865, 0, 0,184716
- , 0, 0,206795, 0, 0,101937, 0, 0, 0,256473
- , 0,101943, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0,112995,112996,112997,101960, 0
- , 0, 0, 0, 0, 0, 0,101968,101969, 0, 0
- ,101972,184758, 0,289621, 0, 0, 0, 0,140613, 0
- ,140615, 0, 0,201327, 0,113025, 0, 0, 0, 0
- , 0, 0, 0,256527, 0, 0,113036, 0, 0, 0
- ,135116, 0, 0,184790, 0,245501,201350,201351, 0, 0
- ,223430,223431, 0,201357, 0, 0, 0,223437,118577,118578
- , 0, 0, 0, 0, 0, 0, 0, 0, 0,107550
- ,184817,184818,184819, 0, 0, 0,184823, 0, 0, 0
- ,107561, 0, 0,184830, 0, 0,184833,184834,184835,184836
- ,184837, 0, 0,184840,184841,184842,184843, 0,184845, 0
- , 0,184848,184849,135179, 0, 0, 0, 0, 0, 0
- ,113110,240048,201416, 0, 0, 0, 0, 0, 0, 0
- , 0,102083, 0, 0, 0, 0, 0, 0, 0,217990
- ,217991, 0, 0, 0, 0, 0,217997, 0, 0, 0
- , 0,135217, 0, 0, 0, 0, 0,135223, 0,229048
- , 0, 0,113152, 0, 0, 0, 0, 0,135234,135235
- , 0, 0,113162,113163,135240, 0, 0, 0, 0, 0
- , 0,135247, 0, 0, 0,57985, 0, 0,13836,80065
- , 0, 0,80068,102145,102146,102147, 0, 0, 0,102151
- , 0, 0,102154, 0,102156, 0, 0,124235, 0,24895
- , 0, 0, 0, 0,267736, 0,173915,267739, 0,184956
- , 0, 0, 0, 0, 0,173924,173925, 0, 0, 0
- ,13878, 0,262235, 0, 0, 0,256720, 0,30443,245685
- , 0, 0, 2852, 0, 0,278805, 0, 0, 0,212581
- , 0,13899, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0,13910, 0,52545,118774, 0,102219, 0, 0
- , 0, 8400, 0,151896, 0, 0,113266,113267, 0, 0
- , 0, 0, 0, 0, 0, 0,273327, 0, 0,13937
- ,13938,13939, 0, 0,13942,13943, 0, 0,13946, 0
- ,13948,80177,80178,80179, 0, 0, 0, 0,13956,13957
- , 0, 0, 0, 0,13962,13963, 0, 0,13966,13967
- , 0, 0,102274,102275, 0,102277, 0, 0,102280,102281
- ,102282,102283,151955,102285,102286, 0, 0,102289, 0, 0
- ,102292, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0,113345, 0, 0, 0, 0
- ,41603, 0, 0, 0, 0, 0,118875, 0, 0, 0
- , 0, 0, 0, 0,135440, 0,118885, 0, 0, 0
- , 0, 0, 0, 0, 0,190641, 0, 0, 0, 0
- , 0, 0, 0,41636,41637, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0,240332, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0,129964, 0, 0
- , 0, 0,41665,41666,41667,41668, 0, 0,41671, 0
- , 0,41674, 0,41676,107905, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0,152079, 0, 0, 0
- , 0,218312,118971, 0, 0, 0, 0, 0, 0, 0
- , 0, 0,284551, 0, 0,41718, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0,41739, 0, 0, 0
- , 0, 0,107973, 0,107975, 0, 0, 0, 0,80385
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0,301157,190778, 0, 0, 0,223896, 0, 0,223899
- , 0, 0,168712, 0, 0,41778, 0, 0,124566, 0
- ,41783, 0, 8671, 0, 0, 0, 0,41790, 0,41792
- , 0, 0,41795,41796,41797, 0,257040,41800, 0,41802
- ,41803, 0,41805,41806,41807,41808, 0, 0, 0,41812
- , 0, 0, 0, 0, 0,30780, 0, 0, 0, 0
- , 0, 0, 0, 0,108055, 0, 0, 0, 0, 0
- ,251555, 0,251557, 0, 0,58395, 0, 0, 0, 0
- , 0,47363, 0, 0, 0, 0, 0, 0, 0, 0
- , 0,163272, 0, 0, 0, 0,229505, 0, 0, 0
- ,251585,251586,251587,251588, 0, 0,251591, 0, 0,251594
- , 0,251596, 0,47395,47396,47397, 0, 0,301274, 0
- , 0, 0,268164,279203, 0, 0, 0, 0,174347, 0
- , 0, 0, 0,268175, 0, 0, 0, 0, 0, 0
- , 0, 0, 0,47425,47426,47427,47428, 0, 0,47431
- , 0, 0, 0,41916, 0, 0, 0, 0, 0, 0
- , 0,268203, 0, 0, 0,30890, 0, 0, 0, 0
- , 0, 0, 0, 0,251659,268217, 0, 0, 0, 0
- , 0, 0, 0, 0, 0,251670,251671, 0,251673, 0
- , 0, 0, 0, 0,246160, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0,251697,251698,251699, 0, 0, 0,251703,268261
- , 0, 0,19909, 0,174443, 0, 0,19914,47510,19916
- , 0, 0,41995, 0, 0,251720,251721,251722,251723, 0
- ,251725,251726, 0, 0,251729, 0,229655,251732, 0, 0
- ,196545, 0, 0, 0, 0,47537,47538,47539, 0, 0
- , 0,47543,262785, 0,218635, 0,36510, 0,240715,218640
- , 0, 0, 0,284872, 0,58595,58596,58597, 0, 0
- , 0, 0,174501,47565,47566,47567,47568,47569, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0,279381, 0, 0, 0,58625,58626,58627,58628,80705
- , 0,58631, 0, 0,58634, 0,58636, 0, 0, 0
- , 0, 0, 0, 0, 0,229734,224216, 0, 0,224219
- , 0, 0, 0,119362, 0,119364, 0,262860, 0,262862
- ,58660, 0, 8991,119372, 0,119374, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0,58678,119388
- ,119389, 0, 0, 0, 0, 0, 0, 0, 0,301525
- , 0, 0, 0, 0,119403, 0, 0,119406, 0,58699
- , 0, 0,119411, 0,119413, 0, 0, 0, 0, 0
- ,58710, 0, 0,119422, 0,268437, 0,268439, 0,119428
- , 0, 0, 0, 0,163585, 0, 0, 0, 0, 0
- , 0,147035, 0, 0, 0, 0, 0,58737,58738,58739
- , 0, 0, 0, 0, 0, 0, 0, 0, 0,58749
- ,58750, 0, 0,58753,58754, 0,58756,58757, 0, 0
- ,58760,58761,58762,58763, 0,58765,58766,58767,58768,58769
- , 0, 0,58772, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0,25671, 0, 0, 0, 0
- ,113980, 0, 0, 0, 0, 0, 0, 0, 0,136065
- ,42243,119510, 0, 0, 0, 0, 0, 0, 0, 0
- ,141595,202305, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0,20194,119537,119538
- ,119539, 0, 0,42276,42277, 0, 0, 0, 0, 0
- , 0, 0, 0,174742, 0, 0, 0, 0, 0, 0
- , 0, 0, 0,263056,263057,42298, 0, 0, 0, 0
- , 0,202355,42305,42306, 0, 0, 0, 0, 0,263072
- , 0, 0, 0, 0, 0,119584, 0,119586,119587, 0
- ,119589, 0,119591,119592, 0, 0,119595, 0,119597, 0
- ,119599, 0, 0, 0,218945, 0,218947,218948,119607, 0
- ,218951, 0, 0,218954,119613,218956, 0,130654,263111, 0
- , 0, 0, 0, 0, 0,235523, 0, 0, 0,257603
- , 0, 0,141707,119632,119633,119634, 0,147231, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- ,296257, 0,92056, 0,14792,92059,75503, 0,235556, 0
- , 0, 0,257636,257637,263157, 0, 0, 0, 0, 0
- ,263163,202455, 0,263166,263167, 0, 0,263170, 0, 0
- ,246616, 0, 0, 0, 0, 0, 0,235585,235586, 0
- , 0,257665, 0, 0,257668, 0,235594,257671,235596, 0
- ,257674,141776, 0, 0,119703, 0, 0,42440,42441,42442
- , 0, 0,42445,42446,42447,42448, 0, 0,219059,42452
- ,141795, 0,219063, 0, 0, 0,252181, 0, 0,141804
- , 0,219072, 0, 0, 0,219076, 0, 0, 0,219080
- ,219081, 0,219083, 0,219085, 0,219087,219088, 0,296356
- ,296357, 0, 0,296360, 0, 0,141831, 0, 0,213581
- , 0,235659, 0, 0, 0,257739, 0, 0, 0, 0
- , 0, 0,235670,59063, 0, 3875, 0, 3877,296385,296386
- ,296387, 0, 0, 0,296391, 0, 0, 0, 0,296396
- , 0, 0, 0, 0, 0,219136, 0,59087, 0, 0
- ,235698, 0,141877,257777,257778, 0, 3906, 3907, 0, 0
- , 0, 0,141887,141888, 0,141890, 0,141892, 0,246755
- ,246756, 0, 0, 0,235722, 0,257800, 0, 0, 0
- , 0, 0,257806,257807, 0,257809, 0,114317,257812, 0
- , 3940,268853, 0, 0,108805, 0, 0,108808, 0, 0
- ,246786,246787, 0, 0,175043, 0,108817, 0, 0, 0
- ,246796, 0,42595, 0,42597, 0, 0, 0, 0, 0
- , 0,108832, 0, 0, 0,296482, 0,219218, 0, 3979
- , 0, 0, 0,108844, 0, 0, 0,175076,175077, 0
- , 0, 0, 0,42626,42627,42628,296503, 0,42631, 0
- , 0,42634,246838,42636, 0, 0, 0, 0, 0, 0
- ,108871, 0, 0,296520,296521,296522, 0, 0, 0, 0
- , 0, 0, 0, 0,153037, 0,197191, 0,136484, 0
- , 4030,197196, 4032, 4033, 0, 0, 4036, 0, 0,219280
- , 4040, 4041, 0, 4043, 0, 4045, 4046, 4047, 4048, 4049
- , 0, 0, 4052,103395,103396,103397,108917, 0,103400,285528
- , 0,246897,246898,246899, 0, 0,42699,246903,108929, 0
- ,108931, 0,53743,197238, 0,59265,246912, 0,246914, 0
- ,246916,246917, 0,103425, 0, 0, 0, 0, 0, 0
- , 0,246927, 0,246929, 0, 0,246932,125515, 0, 0
- , 0,175190, 0, 0,42737, 0, 0, 0, 0, 0
- , 0,191757, 0, 0,191760,136571, 0, 0, 0,42752
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0,42768,42769,26213,197303,42772
- ,97963, 0, 0, 0, 0, 0, 0, 0,197313,197314
- ,197315, 0, 0,175242,175243,197320, 0, 0, 0,175248
- , 0,197326,197327, 0,197329, 0, 0,197332,103510, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- ,103522, 0,230461, 0, 0, 0, 0, 0, 0, 0
- ,53861,136647, 0, 0, 0,103537,103538, 0, 0,26275
- , 0,103543, 0,48355,103546, 0,103548,125625, 0, 0
- , 0,269123, 0, 0, 0, 0, 0, 0, 0, 0
- , 0,103563, 0, 0,103566, 0,103568,103569, 0,142204
- ,103572, 0, 0, 0,48386,48387,48388,70465, 0, 0
- , 0, 0, 0,269155,269156,269157, 0, 0,136704, 0
- ,42883, 0, 0,136709,136710,136711,136712,136713,136714,136715
- ,136716,136717,136718, 0, 0,136721,136722,136723, 0,136725
- , 0,136727, 0, 0, 0, 0,269188, 0, 0,269191
- , 0, 0, 0,42916, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0,175395,175396, 0, 0
- , 0, 0, 0,42946,42947,42948, 0, 0, 0,26395
- , 0,42954, 0,42956,109185, 0, 0, 0, 0,26405
- ,20887, 0, 0, 0, 0, 0, 0,175426,175427,175428
- , 0, 0,175431, 0, 0, 0,48498, 0, 0, 0
- , 0,48503,15390, 0, 0, 0, 0,263750, 0,269271
- , 0,269273,70590, 0,263757, 0, 0, 0, 0, 0
- , 0, 0, 0,109234, 0,48527,48528,48529, 0, 0
- , 0, 0, 0,109244, 0,269297, 0,269299, 0, 0
- , 0,269303, 0, 0, 0,59585, 0,43030, 0, 0
- , 0, 0, 0,15441,15442,15443, 0, 0, 0,269321
- , 0, 0,15450, 0, 0, 0, 0, 0, 0, 0
- ,269332,175510, 0,147917, 0,43058, 0, 0, 0, 0
- ,43063, 0,236230,236231,54105,54106,54107, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0,54122,43085,43086, 0,43088, 0, 0,120357,43092
- , 0, 0, 0, 0,54135,54136, 0, 0,54139,54140
- , 0,175560,175561,175562, 0,32070,175565,175566,175567,175568
- ,175569,10000,32077, 0, 0,153498,120385,120386,120387, 0
- , 0, 0, 0, 0, 0, 0, 0,120396, 0, 0
- , 0, 0,208705, 0, 0, 0, 0, 0, 0, 0
- , 0, 0,54183,54184,54185,54186,54187,54188,54189,54190
- , 0, 0,54193, 0, 0, 0, 0,70755,70756, 0
- ,54201,54202,15570, 0,136990, 0, 0, 0,136994,120438
- ,136996, 0, 0,136999, 0, 4545, 0, 0, 0, 0
- ,114930, 0, 0,137009, 0, 0, 0,70785, 0, 0
- , 0, 0, 0,70791, 0,48717,70794, 0, 0, 0
- ,43203,120470, 0,137029,137030, 0,137032, 0, 0, 0
- ,137036, 0, 0,54254,54255, 0,137042,137043, 0,137045
- , 0,137047, 0,137049,137050,137051, 0, 0,120497,120498
- ,120499, 0,43235,43236, 0, 0, 0, 0, 0, 0
- , 0, 0, 0,120512, 0,120514,120515,120516,120517, 0
- , 0,120520,120521,120522,120523, 0,120525,120526,120527,120528
- ,120529,70859,43265, 0,43267, 0, 0, 0,43271, 0
- , 0,43274,70870,43276,109505, 0,109507,109508,181256,37763
- , 0, 0, 0,59843, 0, 0,181264,65366, 0, 0
- , 0,104003, 0,54334, 0, 0, 0, 0, 0,70897
- ,70898, 0, 0, 0, 0, 0, 0, 0,264071, 0
- , 0,37795,37796,37797,70912, 0,59876,59877, 0,15727
- , 0, 0,70920, 0, 0, 0, 0,70925,70926,70927
- ,70928,70929, 0, 0,70932, 0, 0,54378, 0, 0
- , 0, 0, 0, 0,37828,59905,59906, 0, 0, 0
- , 0, 0,37836,104065, 0, 0, 0,120626,120627, 0
- , 0,302757,104074, 0,104076, 0, 0, 0, 4738,54410
- , 0, 0, 0, 0,43377,43378, 0,10266, 0, 0
- , 0, 0, 0, 0,192400, 0,109617,109618,109619, 0
- ,197925, 0, 0,10282, 0, 0,10285,43400, 0,43402
- ,43403, 0,43405,43406,43407,43408,43409, 0,15816, 0
- , 0, 0, 0, 0, 0,37899, 0, 0, 0,59979
- , 0, 0, 0, 0, 0, 0,37910,104139, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0,104150,32404
- ,32405, 0, 0, 0, 0, 0,142791, 0, 0, 0
- , 0, 0, 0,37937,37938,37939, 0,60017,60018, 0
- , 0, 0, 0,60023, 0,104177,104178, 0, 0, 0
- , 0, 0, 0,60033,60034,60035, 0, 0, 0, 0
- ,60040, 0, 0, 0,37968, 0,60046,60047, 0, 0
- ,104202,104203,60052,104205,104206,104207,104208,104209, 0, 0
- ,104212, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- ,43523, 0, 0,71121, 0,71123,93200, 0, 0, 0
- , 0, 0,71130,71131, 0, 0, 0, 0, 0, 0
- , 0, 0, 0,269825, 0, 0, 0,291905,21475, 0
- ,21477, 0,43555,43556,43557, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0, 0, 0,21505,21506
- , 0,21508,43585,43586, 0,43588, 0,181565,43591, 0
- ,203644,43594, 0,43596, 0, 0,291954, 0, 0, 0
- , 0, 0, 0,60163, 0,10494,176065, 0, 0, 0
- ,198145,104323, 0,10502,10503, 0, 0, 0, 0, 0
- ,76737, 0, 0, 0, 0, 0, 0, 0,192644, 0
- , 0, 0, 0, 0, 0,60195,60196, 0, 0,192655
- ,71238,71239, 0,104355,104356,104357, 0, 0, 0, 0
- , 0,170591,71250,236821, 0, 0, 0,209230, 0, 0
- , 0, 0, 0,21590, 0,60225,60226, 0,60228, 0
- , 0,60231, 0,104385, 0,104387, 0, 0, 0,104391
- , 0, 0,104394, 0, 0,192701, 0, 0, 0,192705
- , 0, 0, 0, 0,43697,43698, 0,236865, 0,236867
- , 0,258945, 0,143048, 0, 0, 0, 0, 0,43712
- , 0, 0, 0, 0,76831, 0,21643,43720, 0,43722
- , 0,21648, 0,43726, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 0, 0, 0,10625, 0,292096,60299
- , 0,281061, 0, 0,54785, 0,54787,104459, 0, 0
- ,60310, 0, 0, 0,76871, 0,176215, 0,104470, 0
- , 0, 5131, 0, 0, 0, 0,148630, 0, 0, 0
- , 0, 0,209345, 0,192790, 0, 0,60337,60338,60339
- , 0, 0,236950, 0,275585, 0,104498,104499, 0,27235
- , 0,104503, 0, 0, 0, 0,60356,60357, 0, 0
- ,60360, 0, 0, 0, 0,60365,60366,60367, 0, 0
- , 0, 0, 0,104525,104526, 0,104528, 0,181796,181797
- ,104532, 0, 0, 0, 0, 0, 0, 0,143173,225959
- ,143175,270113, 0, 0,275635,115585, 0,93511, 0, 0
- ,43843, 0, 0,93517, 0, 0,93520,181825,181826,181827
- ,181828, 0, 0,181831,275655, 0, 0, 0,181836,154242
- , 0, 0, 0, 0, 0, 0, 0,154250,281188,154252
- , 0,154254, 0,43876,43877, 0, 0, 0, 0,248085
- , 0,154264,154265, 0,259128,154268,154269, 0, 0, 0
- ,154273, 0, 0, 0,154277, 0, 0, 0,264661, 0
- , 0,192917, 0, 0, 0, 0,220517, 0, 0,27355
- , 0,43914, 0,43916,110145, 0, 0, 0,27364, 0
- , 0,181899,154305, 0,154307,154308,198461, 0, 0, 0
- , 0, 0,181910,181911, 0, 0,220547,220548, 0, 0
- , 0, 0, 0,220554, 0,220556, 0,237115, 0,154332
- ,204004,204005, 0, 0, 0, 0, 0, 0, 0, 0
- ,181938, 0, 0, 0, 0,181943,198501,126755,126756,126757
- , 0, 0, 0, 0, 0, 0,43979, 0, 0, 0
- , 0, 0,181960,181961,181962,181963, 0, 0,181966,181967
- ,181968, 0,259236,259237,181972, 0, 0,126785,126786,126787
- ,126788,148865, 0,126791, 0, 5375,126794,154390, 0, 0
- , 0, 0,170952, 0,44017, 0,44019, 0, 0,220630
- ,44023,259265,259266,259267,259268,115775, 0,259271, 0,44032
- ,259274, 0, 0, 0, 0,154418, 0, 0, 0,44042
- , 0, 0,44045,44046,44047,44048, 0,220658, 0,44052
- ,126838,275852, 0,121322, 0, 0,121325, 0, 0, 0
- ,275861,220672,220673,220674, 0, 0, 0,121336, 0,220680
- , 0, 0,220683, 0,220685,220686, 0, 0, 0,137905
- ,154463, 0, 0,154466, 0, 0,154469,154470,154471,154472
- ,154473,154474,154475, 0, 0, 0,154479, 0, 0, 0
- , 0, 0, 0, 0, 0,182083,259350,259351, 0, 0
- , 0, 0,220723, 0,121383, 0, 0, 0, 0, 0
- ,121389,121390,121391, 0, 0, 0, 0,126915, 0, 0
- ,154513, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0,126929,248348,248349,126932, 0,11035, 0,71746,248357
- ,93825, 0,248359,71751, 0,259400,71754, 0,259401,248363
- , 0,259402,71756, 0,248366,160062, 0,259405,198696, 0
- ,292523,259409,248371, 0,248373,182145, 0,259412,182146, 0
- ,248382,182154, 0,248385,121448, 0,248387,121450, 0,292541
- ,198718, 0,248412,198741, 0,248421,44218, 0,193236,182198
- , 0,264995,71830, 0,264997,165655, 0,127026,27684, 0
- ,127027,27685, 0,149123,71857, 0,265026,171203, 0,265027
- ,248470, 0,265028,121534,71863, 0,265036,121542, 0,193290
- ,121543,71872, 0,121546,60837, 0,182258,60840, 0,287120
- ,182259, 0,292640,71880, 0,182263,71883, 0,193305,71887
- , 0,248497,149155,71889, 0,248498,149156, 0,248499,149157
- , 0,182272,71892, 0,182273,171235, 0,182274,171236, 0
- ,193313,182275,171237, 0,182280,55343, 0,187802,182283,77422
- ,60865, 0,182285,60867, 0,182286,121577,60868, 0,182287
- ,121578, 0,182288,11199, 0,182289,60871, 0,182292,60874
- , 0,149185,121590, 0,149186,121591, 0,149187,121592,105035
- , 0,171265,27771, 5695, 0,193342,171266, 0,171267,149191
- , 0,254055,149194, 0,248537,171271, 0,248540,171274,94008
- , 0,248541,176794, 0,265099,248542,209909,176795,171276, 0
- ,248543,209910, 0,248544,209911, 0,248545,209912, 0,248546
- ,215432,55381, 0,248550,55385, 0,248551,55386, 0,248552
- ,55387, 0,265110,248553,160249, 0,248554,215440, 0,248558
- ,237520, 0,248567,55402, 0,265137,149238,55415, 0,265138
- ,55416, 0,171318,55419, 0,60939,55420, 0,248593,33352
- , 0,60950,33355, 0,265161,77515, 0,265162,171339, 0
- ,276203,265165,60962, 0,265169,149270, 0,232072,143768,60983
- ,55464, 0,232075,60986,55467, 0,160330,60988,55469, 0
- ,204483,55470, 0,160334,60992,55473, 0,149297,60993,55474
- , 0,149298,60994, 0,149299,60995, 0,171377,60997, 0
- ,171379,149303,55480, 0,61000,55481, 0,116191,61001,55482
- , 0,171383,61003, 0,149312,61008, 0,149313,61009, 0
- ,149315,143796, 0,171392,149316,61012, 0,171393,149317, 0
- ,171396,149320, 0,171397,149321, 0,276261,171400, 0,204515
- ,171401,149325, 5831, 0,204516,171402,149326, 0,204517,171403
- ,149327,49985, 0,171405,149329, 0,171408,149332, 0,210075
- ,204556, 0,226640,182488, 0,292880,270804, 0,199112,110808
- , 0,243267,199115, 0,243268,55622, 0,204659,110836, 0
- ,237781,149477,50135, 0,171556,55657, 0,237785,171557,55658
- , 0,204680,61186, 0,204681,61187, 0,204682,61188,55669
- , 0,204683,55670, 0,204685,61191,55672, 0,204688,61194
- , 0,215727,204689, 0,177100,149505, 0,149506,33607, 0
- ,177102,149507, 0,171587,149511, 0,215757,33630, 0,232323
- ,33639, 0,61259,33664, 0,232356,33672, 0,61270,33675
- , 0,171659,33684, 0,215816,33689, 0,149590,33691, 0
- ,204784,171670, 0,287576,232386,61297, 0,232387,61298, 0
- ,232388,61299, 0,144088,61303, 0,149617, 604, 0,149618
- , 605, 0,149619, 606, 0,171698, 609, 0,171699,149623
- , 0,237929,116511,61321, 0,265526,171703,61323, 0,232414
- ,61325, 0,61326,11655, 0,149643,28225, 0,171721,149645
- ,28227, 0,171722,149646, 0,171723,149647,50305, 0,171725
- ,149649, 0,171728,149652, 0,232459,116560, 0,226960,182808
- ,22757, 0,232497,221459, 0,232498,221460, 0,232503, 705
- , 0,182836,22785, 0,271155,232522, 0,232528,39363, 0
- ,111112,94555, 0,111120,55930, 0,238069,177360, 0,39427
- ,22870, 0,39431,17355, 0,28418,22899, 0,149840,22903
- , 0,166416,22922, 0,166417,22923, 0,33967,22929, 0
- ,144370,33990, 0,166447,39510,33991, 0,171995,39539, 0
- ,188560,116813, 0,298960,39567, 0,194101,39569, 0,149975
- ,144456,94785, 0,249319,166534,144458, 0,166536,116865, 0
- ,243870,116933, 0,243910,172163, 0,243912,199760, 0,243918
- ,39715, 0,243919,39716, 0,128051,39747, 0,243959,39756
- , 0,172225,61845, 0,227416,172226, 0,166756,39819, 0
- ,188835,172278, 0,221976,166786, 0,221979,188865, 0,188867
- ,172310,166791, 0,166794,39857, 0,188871,39858, 0,166796
- ,39859, 0,188876,39863, 0,233032,139209,17791, 0,172337
- ,95071,39881, 0,172338,39882, 0,277200,172339,39883, 0
- ,172342,39886, 0,299280,172343,50925,39887, 0,172344,39888
- , 0,172348,39892, 0,172353,117163, 0,172356,95090, 0
- ,227550,205474,172360, 0,188918,172361, 0,172362,139248, 0
- ,166859,34403, 0,271727,139271, 0,166867,95120, 0,282775
- , 1306, 0,117221, 1322, 0,166897,89631, 0,238648,188977
- , 0,188979,166903, 0,188992,89650, 0,188996,166920, 0
- ,188997,166921, 0,189001,166925, 0,189002,166926, 0,189003
- ,166927, 0,189005,166929, 0,189008,166932, 0,40003,17927
- , 0,89680, 1376, 0,40035,17959, 0,194597,40065, 0
- ,194626,150474, 0,194628,150476,51134, 0,194636,172560, 0
- ,40139,12544, 0,194678,12551, 0,40150,12555, 0,34632
- ,12556, 0,150539,12564, 0,194710,40178, 0,150577, 1564
- , 0,150578, 1565, 0,150579, 1566, 0,117466,40200, 0
- ,117467,40201, 0,40202, 1569, 0,277520,150583,40203, 0
- ,194737,40205, 0,194738,40206, 0,194739,40207, 0,299605
- ,150592,40212, 0,227861,150595, 0,150596,117482, 0,194752
- ,150600, 0,194753,150601, 0,194754,150602, 0,194755,150603
- , 0,194757,150605,139567, 0,194760,150608, 0,194761,150609
- , 0,194762,117496, 0,205803,194765, 0,194766,117500, 0
- ,194767,95425, 0,283096,150640, 0,283099,150643,78896, 0
- ,255507,183760, 0,100987,45797, 0,117547,51319, 0,200392
- ,78974, 0,200395,117610, 0,139701,62435, 0,194923,62467
- ,45910,40391, 0,62468,12797, 0,123203,95608,45937, 0
- ,150800,45939, 0,172880,45943, 0,62518,45961, 0,194981
- ,45968, 0,123235,45969, 0,128755,123236, 0,128775,117737
- , 0,117738,79105, 0,62550,34955, 0,123268,57040, 0
- ,123271,62562, 0,123274,73603, 0,139843,62577,40501, 0
- ,62579,40503, 0,189520,62583, 0,73635,62597, 0,62603
- ,40527, 0,206101,62607, 0,139875,123318,62609, 0,244737
- ,139876, 0,128855,73665, 0,123339,73668, 0,277874,73671
- , 0,139907,123350, 0,123389,112351, 0,123393,24051, 0
- ,300003,123395, 0,140017,40675,18599, 0,140018,40676, 0
- ,140019,40677, 0,195210,73792, 0,206257,195219,73801, 0
- ,206258,195220,73802, 0,206259,195221,73803, 0,195223,73805
- , 0,195224,73806, 0,195225,73807, 0,140040,73812, 0
- ,278016,140041, 0,195233,140043, 0,195237,140047,40705, 0
- ,140048,40706, 0,195239,140049,40707, 0,195246,40714, 0
- ,151120,40740, 0,294616,51780, 0,233925,195292, 0,300181
- ,57345, 0,195350,40818, 0,73955,40841, 0,73956,40842
- , 0,73957,40843, 0,195377,40845, 0,195378,40846, 0
- ,195379,40847, 0,118115,40849, 0,234037,73986, 0,195422
- ,96080, 0,195423,184385, 0,195425,184387, 0,195426,184388
- , 0,195431, 2266, 0,195432, 2267, 0,234066,195433, 0
- ,195438,35387, 0,195447, 2282, 0,300320, 2294, 0,267215
- ,24379, 0,195472,24383, 0,195474,24385, 0,74070,40956
- , 0,289333,267257,223105,118244, 0,223106,118245, 0,223107
- , 2347, 0,223108, 2348, 0,151363,74097, 2350, 0,223111
- ,74098, 0,206555,74099, 2352, 0,223116,74103, 0,151395
- ,74129, 0,151427, 2414, 0,151428, 2415, 0,223179,107280
- , 0,151434,101763, 0,234221,151436, 0,223219,212181, 0
- ,256355,223241, 0,256356,223242, 0,256357,223243,101825, 0
- ,223245,101827,79751, 0,223246,151499,101828, 0,223249,101831
- , 0,223252,101834, 0,162545,101836,79760, 2494, 0,256386
- , 8031, 0,267428,184643,63225, 0,261915,256396, 0,267437
- ,151538, 0,151557,24620, 0,184675,151561, 0,184676,151562
- , 0,184677,151563, 0,267478,118465, 0,267480,118467,101910
- , 0,184707,101922, 0,184714,135043, 0,256470,101938, 0
- ,256471,101939, 0,295120,184740, 0,135075,101961, 0,140595
- ,135076,101962, 0,135077,101963, 0,256497,101965, 2623, 0
- ,256498,101966, 0,256499,101967, 0,256503,24705, 0,256520
- ,113026, 0,256521,245483,113027, 0,256522,113028, 0,256523
- ,135105, 0,135106,19207, 0,256525,135107,118550,113031, 0
- ,256526,184779,135108, 0,256528,113034, 0,256529,135111, 0
- ,256532,135114, 0,223440,118579, 0,278648,113078, 0,184829
- ,135158, 0,245541,184832, 0,184846,113099, 0,184847,140695
- , 0,184852,173814,13763, 0,135190,85519, 0,162808,129694
- ,113137,13795, 0,113138,13796, 0,218000,113139,13797, 0
- ,135218,13800, 0,135219,113143, 0,113153,102115, 0,113154
- ,102116, 0,113155,102117, 0,135232,113156,30371, 0,135233
- ,113157, 0,135236,113160, 0,135237,113161, 0,135241,113165
- , 0,135242,113166, 0,135243,113167,96610,13825, 0,113168
- ,13826, 0,135245,113169,13827, 0,135246,13828, 0,135248
- ,113172, 0,135249,13831, 0,135252,13834, 0,212523,80067
- , 0,102148,35920, 0,140831,102198, 0,113264,80150,13922
- , 0,251243,113268,102230, 0,295413,30501,13944, 0,212636
- ,13952, 0,102257,13953, 0,102258,13954, 0,102259,13955
- , 0,229200,102263, 0,174011,13960, 0,52594,13961, 0
- ,124345,13965, 0,102272,13968, 0,102273,13969, 0,102276
- ,13972, 0,102287,58135, 0,251301,102288, 0,273416,118884
- , 0,41635,19559, 0,80331,52736, 0,240385,201752, 0
- ,240434,41750, 0,268056,41777, 0,174235,41779, 0,240477
- ,41793, 0,240478,41794, 0,251523,41801, 0,141151,41809
- , 0,251556,229480,223961, 0,251572,97040, 0,301275,273680
- , 0,268221,80575, 0,251727,152385, 0,251728,58563, 0
- ,262788,240712, 0,284880,47563, 0,279421,119370, 0,268388
- ,119375, 0,268397,119384, 0,257360,119385, 0,119393,20051
- , 0,301524,119397, 0,251873,75265, 0,224281,53192, 0
- ,268438,119425,53197, 0,268440,119427,97351, 0,119452,58743
- , 0,119461,58752, 0,102907,58755, 0,218883,42275, 0
- ,290640,263045,20209, 0,279605,263048, 0,240991,218915,42307
- , 0,218916,42308, 0,218917,20233, 0,119577,42311, 0
- ,119580,42314,20238, 0,263075,119581, 0,119582,42316, 0
- ,163735,119583, 0,119585,58876, 0,202373,119588, 0,263084
- ,202375,119590,108552, 0,263087,119593, 0,263088,119594, 0
- ,119596,64406, 0,119598,108560, 0,218946,80971, 0,241040
- ,69951, 0,301772,42379, 0,218994,81019, 0,235555,218998
- ,42390, 0,235557,81025, 0,257635,58951, 0,263168,169345
- , 0,263169,224536, 0,263171,219019, 0,263172,224539, 0
- ,263176,246619, 0,263177,42417, 0,263178,42418, 0,147280
- ,42419, 0,235587,219030, 0,263183,235588,141765,42423, 0
- ,263185,257666, 0,263186,257667,235591,141768, 0,136255,42432
- , 0,257676,141777,119701, 0,285279,42443, 0,296323,219057
- ,42449,20373, 0,219058,141792, 0,219073,141807, 0,219074
- ,141808, 0,219075,53505, 0,219077,31431, 0,224601,219082
- , 0,169413, 3843, 0,219086,169415, 0,296355,219089, 0
- ,219092,197016, 0,197019,97677, 0,257750, 3876, 0,296388
- ,274312, 0,296394,246723, 0,235697,174988, 0,235699,174990
- , 0,257779,235703, 3905, 0,141883, 3908, 0,257783,25985
- , 0,141886, 3911, 0,141889, 3914, 0,141891, 3916, 0
- ,246757,141896, 0,235720,141897, 0,235721,141898, 0,235723
- ,169495, 0,257801,235725, 0,257802,235726,141903, 0,257803
- ,235727, 0,235728,141905,114310,42563, 0,257805,235729,141906
- ,114311, 0,257808,235732, 0,279896,42579, 0,279899,246785
- , 0,296459,246788, 0,246791,108816, 0,246794,197123, 3958
- , 0,296470,42596, 0,175075,108847, 0,296497,197155, 3990
- , 0,296498,197156, 0,296499,197157,42625, 0,296523,175105
- , 0,175106,153030, 4017, 0,296525,175107,153031, 4018, 0
- ,296526,175108,136475, 4019, 0,296527,197185, 0,296528,197186
- ,103363, 0,296529,197187,175111, 0,246859,197188, 4023, 0
- ,296532,175114, 0,175116,153040, 0,197194,136485, 4029, 0
- ,246870, 4034, 0,153048, 4035, 0,130974, 4037, 0,97865
- , 4042, 0,246913,42710, 0,246915,81345, 0,246920,103426
- , 0,246921,108946,103427, 0,246922,103428, 0,285556,246923
- , 0,257963,246925,103431, 0,246926,235888,175179,86875, 0
- ,246928,103434, 0,197259,103436, 0,169672,86887, 0,197270
- ,42738, 0,147600,42739, 0,169680,42743, 0,246963,42760
- , 0,175217,42761, 0,175218,42762, 0,280080,175219,42763
- , 0,197297,53803,42765, 0,197298,42766, 0,197299,175223
- ,42767, 0,258021,197312, 0,197316,175240, 0,197317,175241
- , 0,197321,186283,175245, 4156, 0,197322,175246,103499, 0
- ,197323,175247, 0,197325,175249, 0,197328,175252, 0,142145
- ,75917, 0,208400,103539, 0,197363,98021, 0,252560,48357
- , 0,186341,136670, 0,136674,103560, 0,142194,103561, 0
- ,136676,103562, 0,136679,103565, 0,247061,103567, 0,136689
- ,48385, 0,180847,48391, 0,114620,109101, 0,269185,136729
- , 0,269186,175363,136730, 0,269187,136731, 0,269194,42915
- , 0,269196,202968,42917, 0,197473,175397, 0,202996,42945
- , 0,48470,42951, 0,180936,26404, 0,180944,175425, 0
- ,175434,48497, 0,269259,175436,48499, 0,269270,263751,15396
- , 0,285840,236169,48523, 0,274817,269298,43019, 0,269320
- ,15446, 0,269322,175499,87195, 0,269323,15449, 0,269325
- ,15451, 0,269326,258288, 0,269327,26491, 0,269328,147910
- , 0,269329,230696,147911, 0,120323,43057, 0,147920,43059
- , 0,236237,43072, 0,43080,21004, 0,175537,43081, 0
- ,175538,43082, 0,175539,43083, 0,175543,54125,43087, 0
- ,120355,43089, 0,120356,21014, 0,175563,54145, 0,175572
- ,153496, 0,120388,98312, 0,120391,76239, 0,120394,70723
- , 0,136967,54182, 0,54191,15558, 0,54192,15559, 0
- ,219764,54194, 0,70757,54200, 0,203231, 4547, 0,70786
- ,48710, 0,181167,70787,48711, 0,120459,70788, 0,137024
- ,70796, 0,137031,54246, 0,137033,54248, 0,137034,54249
- , 0,137035,54250, 0,137037,54252, 0,137038,54253, 0
- ,137041,54256, 0,120503,43237, 0,297121,120513, 0,120532
- ,43266, 0,175724,43268, 0,70899,54342, 0,76419,54343
- , 0,109534,76420,54344, 0,70903,54346, 0,208888,59875
- , 0,104035,70921, 0,104036,70922, 0,104037,70923, 0
- ,54377,43339, 0,280661,37825, 0,37826,15750, 0,37827
- ,15751, 0,59907,43350,37831, 0,59908,54389, 0,54390
- ,15757, 0,54391,37834, 0,59911,54392, 0,104066,59914
- , 0,120624,104067, 0,104068,59916, 0,120628,109590,104071
- , 0,148240,43379, 0,197915,43383, 0,197924,43392, 0
- ,59958,43401, 0,208982,43412, 0,275231,59990, 0,60019
- ,37943, 0,236635,104179, 0,231120,104183, 0,71070,60032
- , 0,198011,60036,37960, 0,60037,37961, 0,302874,71076
- ,37962, 0,302875,37963, 0,115231,60041,37965, 0,60042
- ,37966, 0,60043,37967, 0,60045,37969, 0,104200,60048
- ,37972, 0,104201,60049, 0,142869,71122, 0,203585,71129
- , 0,203634,21507, 0,43587,21511, 0,109840,54650, 0
- ,264392,220240, 0,264400,60197, 0,280975,209228, 0,176115
- ,43659, 0,192683,60227,43670, 0,176133,104386,60234, 0
- ,176135,104388,60236, 0,192697,148545, 0,281003,148547, 0
- ,165105,148548,104396, 0,247896,21617, 0,192707,21618, 0
- ,192708,21619, 0,43699,21623, 0,236868,43703, 0,60278
- ,43721, 0,43723,21647, 0,43725,21649, 0,303120,43727
- , 0,192741,43728, 0,270008,43729, 0,43732, 5099, 0
- ,143105,32725, 0,143128,60343, 0,181763,104497, 0,253517
- ,60352, 0,198328,148657,60353, 0,148658,60354, 0,148659
- ,60355, 0,192817,60361, 0,192818,60362, 0,192819,60363
- , 0,104520,60368, 0,236977,225939,104521,60369, 0,236978
- ,143155,104522, 0,236979,104523, 0,143157,60372, 0,104527
- , 5185, 0,181795,104529, 0,275653,192868, 0,192872,181834
- , 0,192877,154244, 0,220483,154255,43875, 0,192918,43905
- , 0,192919,154286,43906, 0,220515,192920,43907, 0,220516
- ,43908, 0,198443,154291,43911, 0,154293,143255, 0,281239
- ,154302, 0,275735,220545, 0,220546,181913,126723, 0,220551
- ,54981, 0,203995,176400, 0,259203,181937, 0,181939,10850
- , 0,220598,181965,43990, 0,259235,181969, 0,220619,126796
- , 0,170955,44018, 0,259276,226162,121301, 0,154417,77151
- , 0,154419,121305, 0,204091,121306,44040, 0,121307,44041
- , 0,281360,44043, 0,220657,44049, 0,220659,209621, 0
- ,220663,209625, 0,220675,55105, 0,220676,143410, 0,220677
- ,121335, 0,259314,220681,121339, 0,220682,126859,121340, 0
- ,220687,121345, 0,220688,154460, 0,220689,154461, 0,220692
- ,154464, 0,275883,154465,126870, 0,165505,154467, 0,154468
- ,71683, 0,187590,154476, 0,187591,154477, 0,259339,154478
- ,143440, 0,275901,187597, 0,275905,154487, 0,259353,126897
- , 0,154493,126898, 0,231760,126899, 0,121382,49635, 0
- ,126903,121384, 0,248322,121385, 0,121386,71715, 0,248324
- ,121387,71716, 0,121388,71717, 0,160025,121392, 0,248330
- ,126912,121393, 0,126913,121394, 0,248332,126914, 0,248334
- ,126916, 0,248335,154512,126917, 0,160033,154514,121400, 0
- ,126920,121401, 0,259377,248339,126921,121402, 0,259378,126922
- , 0,259379,248341,126923, 5505, 0,182115,126925, 0,286977
- ,248344,182116,126926, 0,259383,248345,182117,126927, 0,275941
- ,126928, 0,248353,71745, 0) ;
- --| Hash values to check against to verify that
- --| correct action has been found for this
- --| parser state and input token.
- -- NYU Reference Name: ACTION_TABLE2
-
- DefaultMap :
- constant array (DefaultMapRange) of GC.ParserInteger :=
- ( 1411, 0, 0, 0, 0, 1409, 0, 1233, 953, 1222
- , 1410, 0, 1224, 0, 1417, 0, 0, 0, 1226, 1227
- , 1228, 1229, 1230, 1231, 0, 0, 0, 0, 1225, 1232
- , 0, 0, 0, 1286, 1105, 0, 1106, 1088, 0, 1087
- , 1049, 1048, 0, 1103, 1104, 0, 1333, 1353, 1089, 1050
- , 1051, 1052, 1092, 1071, 1339, 1074, 1075, 1076, 1077, 1078
- , 1079, 1082, 1083, 1357, 1362, 1360, 0, 1093, 1090, 1091
- , 0, 1336, 1170, 1171, 0, 1251, 0, 1169, 1185, 1165
- , 0, 1286, 1164, 1180, 1286, 1286, 1248, 0, 0, 1249
- , 1250, 0, 1235, 1236, 1413, 1412, 1299, 1114, 986, 1298
- , 0, 0, 1047, 0, 0, 1089, 1319, 0, 1330, 1328
- , 1070, 0, 1355, 0, 1096, 1094, 1098, 0, 1095, 1099
- , 1097, 1080, 0, 0, 0, 0, 0, 0, 1335, 0
- , 1073, 0, 0, 0, 0, 0, 0, 0, 0, 1102
- , 1100, 1101, 0, 1109, 1110, 1107, 1108, 0, 1111, 1084
- , 0, 1089, 1085, 1358, 0, 0, 0, 0, 0, 1296
- , 0, 1418, 1186, 0, 1301, 0, 0, 1321, 1030, 0
- , 1386, 0, 0, 0, 1377, 0, 1286, 0, 0, 1287
- , 0, 1286, 0, 0, 0, 0, 0, 0, 1086, 0
- , 0, 1026, 0, 1064, 0, 1065, 1330, 1223, 1356, 1334
- , 1013, 1081, 1354, 992, 1062, 1061, 1063, 1060, 1059, 1112
- , 1113, 0, 1055, 1056, 1058, 1057, 1054, 1339, 1337, 0
- , 0, 1353, 1343, 0, 1345, 1347, 1344, 1346, 1348, 0
- , 0, 1359, 1361, 1363, 0, 1167, 1298, 0, 1384, 0
- , 1419, 970, 1175, 0, 1384, 0, 0, 1303, 0, 0
- , 0, 0, 0, 0, 954, 1032, 955, 956, 957, 958
- , 959, 960, 961, 962, 963, 964, 0, 971, 972, 973
- , 1286, 1286, 1033, 1034, 1042, 1043, 1044, 1045, 1046, 0
- , 0, 0, 1274, 1275, 1276, 1277, 1290, 1152, 1387, 1388
- , 0, 0, 1377, 0, 1286, 0, 0, 1377, 1378, 0
- , 0, 1234, 953, 0, 1389, 1414, 0, 1117, 1116, 1300
- , 1342, 1338, 1332, 1325, 1328, 1069, 1025, 0, 0, 1326
- , 1328, 1331, 0, 1068, 0, 0, 1053, 1072, 1341, 1340
- , 1349, 1351, 1350, 1352, 0, 1175, 0, 1173, 0, 0
- , 0, 0, 0, 0, 1176, 1294, 0, 0, 0, 1241
- , 0, 1302, 0, 0, 1268, 1047, 0, 1052, 1169, 0
- , 0, 0, 1197, 0, 0, 1323, 1031, 1322, 1286, 0
- , 1286, 1196, 0, 0, 1178, 0, 1264, 1181, 0, 0
- , 0, 1184, 1237, 952, 0, 0, 1115, 1330, 1024, 1320
- , 1327, 1330, 1329, 1014, 993, 0, 1266, 1174, 1294, 0
- , 0, 0, 0, 0, 0, 0, 1261, 0, 0, 1006
- , 1262, 1263, 1005, 0, 0, 1315, 1421, 1420, 1255, 1297
- , 1177, 0, 0, 1166, 0, 1286, 0, 0, 1273, 1422
- , 1270, 0, 1424, 1304, 0, 0, 0, 0, 0, 0
- , 1198, 1286, 0, 0, 1028, 0, 0, 0, 1294, 1294
- , 984, 1036, 1037, 1038, 1039, 1041, 1035, 1040, 1286, 0
- , 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
- , 0, 0, 0, 1290, 1047, 0, 1291, 0, 1290, 1119
- , 1120, 0, 1123, 1124, 1125, 1126, 1127, 1128, 1129, 1130
- , 1131, 1132, 1133, 1134, 1135, 1136, 1137, 1138, 1366, 0
- , 0, 1206, 1207, 1208, 1153, 1292, 1422, 1377, 1183, 0
- , 0, 1191, 1067, 1066, 1422, 1172, 0, 1385, 1027, 984
- , 0, 0, 1259, 1258, 1260, 1257, 0, 1253, 0, 0
- , 1295, 1252, 0, 0, 0, 0, 1286, 0, 0, 0
- , 0, 0, 1286, 1286, 1391, 1393, 0, 0, 0, 0
- , 0, 1286, 0, 0, 976, 977, 978, 979, 980, 981
- , 982, 998, 999, 1000, 1307, 1307, 1315, 0, 0, 1294
- , 1294, 0, 1242, 0, 0, 0, 0, 985, 987, 988
- , 989, 1324, 1238, 1195, 1239, 1407, 1399, 0, 0, 0
- , 1157, 0, 0, 1143, 1369, 0, 1140, 1246, 0, 1161
- , 0, 0, 1403, 0, 0, 0, 1179, 0, 1364, 0
- , 1121, 1122, 1367, 0, 1290, 0, 0, 1286, 1377, 0
- , 0, 0, 1182, 0, 1390, 0, 1168, 1309, 1089, 1311
- , 1012, 0, 1256, 1294, 0, 0, 1286, 0, 0, 1425
- , 0, 0, 1426, 0, 1286, 0, 1279, 1278, 1194, 983
- , 0, 1377, 1393, 0, 0, 1286, 1004, 1002, 0, 991
- , 1189, 0, 0, 1313, 996, 997, 1305, 995, 974, 1308
- , 1001, 1003, 0, 1089, 0, 0, 0, 0, 965, 967
- , 0, 0, 0, 0, 0, 1292, 1205, 0, 0, 1159
- , 1163, 1371, 1290, 1247, 1162, 0, 0, 0, 1290, 1290
- , 1290, 1211, 1212, 1213, 1214, 1371, 1139, 0, 0, 1290
- , 0, 0, 1149, 1290, 1377, 0, 0, 1293, 1382, 1381
- , 1154, 0, 951, 0, 0, 0, 1011, 0, 1008, 1020
- , 0, 1316, 1269, 1423, 1284, 0, 0, 0, 1286, 0
- , 1240, 0, 0, 1395, 1377, 1286, 1392, 1187, 1286, 0
- , 0, 0, 0, 969, 966, 968, 1193, 1192, 990, 0
- , 1220, 0, 0, 1384, 1290, 1203, 0, 1158, 0, 1290
- , 0, 0, 1368, 1290, 0, 0, 1406, 1216, 0, 1215
- , 1290, 0, 1285, 1141, 1365, 0, 0, 0, 0, 1156
- , 1245, 1244, 1415, 1383, 1265, 1267, 0, 0, 1009, 1010
- , 0, 0, 0, 0, 0, 1427, 0, 1201, 1377, 0
- , 0, 1199, 1394, 1018, 1015, 0, 0, 1286, 1286, 994
- , 0, 0, 1029, 1408, 1401, 0, 0, 0, 1373, 1160
- , 1372, 0, 0, 1217, 0, 1290, 1290, 0, 1404, 0
- , 0, 1150, 1377, 0, 1155, 0, 0, 1310, 0, 1312
- , 1254, 1283, 1280, 0, 0, 1200, 0, 1384, 1202, 0
- , 0, 0, 1017, 1306, 0, 0, 0, 0, 1400, 1377
- , 0, 1319, 0, 1290, 0, 1210, 0, 0, 0, 1151
- , 0, 1377, 0, 1290, 1007, 0, 0, 1281, 1397, 0
- , 1288, 1294, 0, 1190, 975, 1384, 0, 1290, 0, 0
- , 1374, 1370, 1142, 0, 0, 1209, 1147, 0, 1416, 1243
- , 1282, 0, 1396, 0, 0, 1188, 0, 1204, 1146, 1290
- , 0, 0, 0, 1148, 1384, 0, 1289, 1317, 1019, 1402
- , 1145, 1144, 1218, 0, 0, 0, 1319, 0, 1219, 1398
- , 1286, 0, 0, 1318, 1023, 1286, 0, 1022, 1021) ;
- --| Map of states (constant array ) to default reductions.
- -- NYU Reference Name: DEFAULT
-
- type FollowSymbolIndexArray is array ( PositiveParserInteger range <>)
- of GC.ParserInteger ;
-
- FollowSymbolMapIndex : constant FollowSymbolIndexArray :=
- ( 1, 1, 2, 2, 3, 4, 5, 5, 6, 45
- , 46, 59, 60, 73, 74, 87, 88, 101, 102, 115
- , 116, 132, 133, 149, 150, 163, 164, 180, 181, 194
- , 195, 211, 212, 225, 226, 226, 227, 228, 229, 230
- , 231, 232, 233, 239, 240, 241, 242, 255, 256, 269
- , 270, 283, 284, 284, 285, 286, 287, 288, 289, 289
- , 290, 290, 291, 291, 292, 292, 293, 293, 294, 294
- , 295, 295, 296, 329, 330, 331, 332, 365, 366, 372
- , 373, 374, 375, 376, 377, 398, 399, 400, 401, 402
- , 403, 404, 405, 407, 408, 409, 410, 412, 413, 413
- , 414, 415, 416, 417, 418, 418, 419, 452, 453, 455
- , 456, 457, 458, 467, 468, 469, 470, 490, 491, 492
- , 493, 497, 498, 500, 501, 502, 503, 504, 505, 506
- , 507, 508, 509, 510, 511, 523, 524, 525, 526, 534
- , 535, 542, 543, 556, 557, 570, 571, 586, 587, 595
- , 596, 607, 608, 616, 617, 628, 629, 640, 641, 652
- , 653, 686, 687, 720, 721, 755, 756, 789, 790, 824
- , 825, 825, 826, 855, 856, 857, 858, 858, 859, 860
- , 861, 862, 863, 863, 864, 865, 866, 867, 868, 869
- , 870, 879, 880, 887, 888, 895, 896, 903, 904, 911
- , 912, 919, 920, 929, 930, 940, 941, 965, 966, 994
- , 995, 1019, 1020, 1049, 1050, 1078, 1079, 1107, 1108, 1114
- , 1115, 1144, 1145, 1174, 1175, 1204, 1205, 1215, 1216, 1224
- , 1225, 1233, 1234, 1242, 1243, 1249, 1250, 1286, 1287, 1314
- , 1315, 1341, 1342, 1367, 1368, 1373, 1374, 1400, 1401, 1427
- , 1428, 1447, 1448, 1474, 1475, 1501, 1502, 1528, 1529, 1555
- , 1556, 1582, 1583, 1609, 1610, 1636, 1637, 1663, 1664, 1690
- , 1691, 1717, 1718, 1744, 1745, 1771, 1772, 1798, 1799, 1825
- , 1826, 1852, 1853, 1879, 1880, 1899, 1900, 1902, 1903, 1905
- , 1906, 1906, 1907, 1910, 1911, 1912, 1913, 1914, 1915, 1916
- , 1917, 1919, 1920, 1920, 1921, 1921, 1922, 1924, 1925, 1927
- , 1928, 1928, 1929, 1930, 1931, 1933, 1934, 1937, 1938, 1939
- , 1940, 1941, 1942, 1944, 1945, 1945, 1946, 1946, 1947, 1947
- , 1948, 1948, 1949, 1949, 1950, 1950, 1951, 1952, 1953, 1953
- , 1954, 1956, 1957, 1958, 1959, 1959, 1960, 1963, 1964, 1965
- , 1966, 1992, 1993, 2019, 2020, 2046, 2047, 2049, 2050, 2052
- , 2053, 2055, 2056, 2058, 2059, 2061, 2062, 2064, 2065, 2067
- , 2068, 2069, 2070, 2077, 2078, 2079, 2080, 2087, 2088, 2092
- , 2093, 2100, 2101, 2108, 2109, 2114, 2115, 2116, 2117, 2118
- , 2119, 2126, 2127, 2128, 2129, 2130, 2131, 2132, 2133, 2134
- , 2135, 2135, 2136, 2138, 2139, 2144, 2145, 2150, 2151, 2151
- , 2152, 2152, 2153, 2155, 2156, 2157, 2158, 2159, 2160, 2161
- , 2162, 2162, 2163, 2164, 2165, 2178, 2179, 2192, 2193, 2206
- , 2207, 2220, 2221, 2224, 2225, 2229, 2230, 2234, 2235, 2236
- , 2237, 2238, 2239, 2240, 2241, 2247) ;
-
- FollowSymbolMap : constant FollowSymbolArray :=
- ( 96, 96, 71, 80, 72, 2, 4, 10, 12, 14
- , 15, 19, 20, 21, 22, 23, 24, 25, 26, 27
- , 28, 29, 33, 37, 39, 42, 43, 44, 45, 46
- , 51, 53, 54, 55, 56, 57, 59, 60, 61, 62
- , 63, 65, 67, 68, 92, 10, 21, 25, 26, 27
- , 42, 43, 44, 45, 55, 56, 59, 60, 65, 10
- , 21, 25, 26, 27, 42, 43, 44, 45, 55, 56
- , 59, 60, 65, 10, 21, 25, 26, 27, 42, 43
- , 44, 45, 55, 56, 59, 60, 65, 10, 21, 25
- , 26, 27, 42, 43, 44, 45, 55, 56, 59, 60
- , 65, 10, 21, 25, 26, 27, 42, 43, 44, 45
- , 55, 56, 59, 60, 65, 10, 21, 25, 26, 27
- , 42, 43, 44, 45, 54, 55, 56, 59, 60, 63
- , 65, 96, 10, 21, 25, 26, 27, 42, 43, 44
- , 45, 54, 55, 56, 59, 60, 63, 65, 96, 10
- , 21, 25, 26, 27, 42, 43, 44, 45, 55, 56
- , 59, 60, 65, 10, 21, 25, 26, 27, 42, 43
- , 44, 45, 54, 55, 56, 59, 60, 63, 65, 96
- , 10, 21, 25, 26, 27, 42, 43, 44, 45, 55
- , 56, 59, 60, 65, 10, 21, 25, 26, 27, 42
- , 43, 44, 45, 54, 55, 56, 59, 60, 63, 65
- , 96, 10, 21, 25, 26, 27, 42, 43, 44, 45
- , 55, 56, 59, 60, 65, 79, 80, 88, 72, 80
- , 80, 88, 31, 33, 58, 72, 75, 80, 85, 75
- , 79, 10, 21, 25, 26, 27, 42, 43, 44, 45
- , 55, 56, 59, 60, 65, 10, 21, 25, 26, 27
- , 42, 43, 44, 45, 55, 56, 59, 60, 65, 10
- , 21, 25, 26, 27, 42, 43, 44, 45, 55, 56
- , 59, 60, 65, 80, 72, 80, 72, 80, 80, 80
- , 80, 80, 80, 80, 80, 7, 16, 17, 30, 31
- , 33, 34, 36, 39, 47, 49, 50, 58, 64, 69
- , 71, 72, 73, 74, 75, 76, 78, 80, 81, 82
- , 83, 84, 85, 86, 87, 88, 89, 90, 91, 80
- , 88, 7, 16, 17, 30, 31, 33, 34, 36, 39
- , 47, 49, 50, 58, 64, 69, 71, 72, 73, 74
- , 75, 76, 78, 80, 81, 82, 83, 84, 85, 86
- , 87, 88, 89, 90, 91, 33, 72, 75, 80, 84
- , 85, 88, 80, 88, 80, 88, 7, 30, 31, 33
- , 36, 39, 47, 58, 64, 72, 75, 80, 81, 82
- , 83, 84, 85, 86, 88, 89, 90, 91, 72, 75
- , 72, 75, 72, 75, 47, 80, 88, 80, 88, 47
- , 80, 88, 80, 72, 75, 72, 75, 38, 7, 9
- , 30, 31, 33, 34, 36, 39, 47, 49, 58, 64
- , 69, 70, 71, 72, 73, 74, 75, 76, 77, 78
- , 80, 81, 82, 83, 84, 85, 86, 87, 88, 89
- , 90, 91, 33, 72, 75, 72, 75, 7, 31, 33
- , 39, 58, 64, 72, 75, 80, 85, 21, 61, 10
- , 12, 21, 22, 25, 26, 27, 42, 43, 44, 45
- , 54, 55, 56, 59, 60, 61, 63, 65, 67, 68
- , 12, 65, 12, 21, 43, 61, 65, 21, 43, 61
- , 43, 61, 21, 61, 21, 61, 84, 85, 84, 85
- , 10, 21, 25, 26, 27, 42, 44, 45, 55, 56
- , 59, 60, 65, 10, 21, 10, 21, 26, 27, 42
- , 43, 45, 56, 60, 10, 21, 26, 27, 42, 45
- , 56, 60, 10, 21, 25, 26, 27, 42, 43, 44
- , 45, 55, 56, 59, 60, 65, 10, 21, 25, 26
- , 27, 42, 43, 44, 45, 55, 56, 59, 60, 65
- , 10, 21, 25, 26, 27, 42, 43, 44, 45, 54
- , 55, 56, 59, 60, 63, 65, 10, 21, 26, 27
- , 42, 43, 45, 56, 60, 10, 21, 26, 27, 42
- , 43, 45, 54, 56, 60, 63, 96, 10, 21, 26
- , 27, 42, 43, 45, 56, 60, 10, 21, 26, 27
- , 42, 43, 45, 54, 56, 60, 63, 96, 10, 21
- , 26, 27, 42, 43, 45, 54, 56, 60, 63, 96
- , 10, 21, 26, 27, 42, 43, 45, 54, 56, 60
- , 63, 96, 7, 9, 30, 31, 33, 34, 36, 39
- , 47, 49, 58, 64, 69, 70, 71, 72, 73, 74
- , 75, 76, 77, 78, 80, 81, 82, 83, 84, 85
- , 86, 87, 88, 89, 90, 91, 7, 9, 30, 31
- , 33, 34, 36, 39, 47, 49, 58, 64, 69, 70
- , 71, 72, 73, 74, 75, 76, 77, 78, 80, 81
- , 82, 83, 84, 85, 86, 87, 88, 89, 90, 91
- , 7, 9, 30, 31, 33, 34, 36, 39, 47, 49
- , 58, 60, 64, 69, 70, 71, 72, 73, 74, 75
- , 76, 77, 78, 80, 81, 82, 83, 84, 85, 86
- , 87, 88, 89, 90, 91, 7, 9, 30, 31, 33
- , 34, 36, 39, 47, 49, 58, 64, 69, 70, 71
- , 72, 73, 74, 75, 76, 77, 78, 80, 81, 82
- , 83, 84, 85, 86, 87, 88, 89, 90, 91, 7
- , 9, 30, 31, 33, 34, 36, 39, 47, 49, 58
- , 60, 64, 69, 70, 71, 72, 73, 74, 75, 76
- , 77, 78, 80, 81, 82, 83, 84, 85, 86, 87
- , 88, 89, 90, 91, 72, 7, 30, 31, 33, 34
- , 36, 39, 47, 49, 58, 64, 69, 72, 73, 74
- , 75, 76, 78, 80, 81, 82, 83, 84, 85, 86
- , 87, 88, 89, 90, 91, 72, 75, 72, 72, 75
- , 72, 75, 72, 72, 75, 72, 75, 72, 75, 7
- , 31, 33, 39, 58, 64, 72, 75, 80, 85, 7
- , 31, 33, 58, 72, 75, 80, 85, 31, 33, 39
- , 58, 72, 75, 80, 85, 31, 33, 58, 64, 72
- , 75, 80, 85, 7, 31, 33, 58, 72, 75, 80
- , 85, 31, 33, 39, 58, 72, 75, 80, 85, 7
- , 31, 33, 39, 58, 64, 72, 75, 80, 85, 3
- , 35, 36, 37, 65, 66, 67, 68, 71, 74, 76
- , 7, 30, 31, 33, 36, 39, 47, 58, 64, 69
- , 72, 74, 75, 76, 80, 81, 82, 83, 84, 85
- , 86, 88, 89, 90, 91, 7, 30, 31, 33, 34
- , 36, 39, 47, 49, 58, 64, 69, 72, 73, 74
- , 75, 76, 78, 80, 81, 82, 83, 84, 85, 86
- , 88, 89, 90, 91, 7, 30, 31, 33, 36, 39
- , 47, 58, 64, 69, 72, 74, 75, 76, 80, 81
- , 82, 83, 84, 85, 86, 88, 89, 90, 91, 7
- , 30, 31, 33, 34, 36, 39, 47, 49, 58, 64
- , 69, 72, 73, 74, 75, 76, 78, 80, 81, 82
- , 83, 84, 85, 86, 87, 88, 89, 90, 91, 7
- , 30, 31, 33, 34, 36, 39, 47, 49, 58, 64
- , 69, 72, 73, 74, 75, 76, 78, 80, 81, 82
- , 83, 84, 85, 86, 88, 89, 90, 91, 7, 30
- , 31, 33, 34, 36, 39, 47, 49, 58, 64, 69
- , 72, 73, 74, 75, 76, 78, 80, 81, 82, 83
- , 84, 85, 86, 88, 89, 90, 91, 35, 37, 65
- , 66, 67, 68, 71, 7, 30, 31, 33, 34, 36
- , 39, 47, 49, 58, 64, 69, 72, 73, 74, 75
- , 76, 78, 80, 81, 82, 83, 84, 85, 86, 87
- , 88, 89, 90, 91, 7, 30, 31, 33, 34, 36
- , 39, 47, 49, 58, 64, 69, 72, 73, 74, 75
- , 76, 78, 80, 81, 82, 83, 84, 85, 86, 87
- , 88, 89, 90, 91, 7, 30, 31, 33, 34, 36
- , 39, 47, 49, 58, 64, 69, 72, 73, 74, 75
- , 76, 78, 80, 81, 82, 83, 84, 85, 86, 87
- , 88, 89, 90, 91, 3, 35, 36, 37, 65, 66
- , 67, 68, 71, 74, 76, 3, 35, 36, 37, 65
- , 66, 67, 68, 71, 3, 35, 36, 37, 65, 66
- , 67, 68, 71, 3, 35, 36, 37, 65, 66, 67
- , 68, 71, 35, 37, 65, 66, 67, 68, 71, 7
- , 16, 17, 30, 31, 33, 34, 36, 39, 47, 49
- , 50, 58, 61, 64, 69, 70, 71, 72, 73, 74
- , 75, 76, 77, 78, 80, 81, 82, 83, 84, 85
- , 86, 87, 88, 89, 90, 91, 2, 4, 10, 12
- , 14, 15, 19, 20, 21, 23, 24, 25, 28, 29
- , 33, 37, 39, 43, 46, 51, 53, 57, 61, 62
- , 65, 67, 68, 92, 2, 4, 10, 12, 14, 15
- , 19, 20, 21, 23, 24, 25, 28, 29, 33, 37
- , 39, 43, 46, 51, 53, 61, 62, 65, 67, 68
- , 92, 2, 4, 10, 12, 14, 15, 19, 20, 21
- , 23, 24, 25, 28, 29, 33, 37, 39, 46, 51
- , 53, 61, 62, 65, 67, 68, 92, 19, 20, 21
- , 23, 39, 61, 2, 4, 10, 12, 14, 15, 19
- , 20, 21, 23, 24, 25, 28, 29, 33, 37, 39
- , 43, 46, 51, 53, 61, 62, 65, 67, 68, 92
- , 2, 4, 10, 12, 14, 15, 19, 20, 21, 23
- , 24, 25, 28, 29, 33, 37, 39, 43, 46, 51
- , 53, 61, 62, 65, 67, 68, 92, 2, 4, 10
- , 12, 14, 15, 24, 25, 28, 29, 33, 37, 46
- , 51, 53, 62, 65, 67, 68, 92, 2, 4, 10
- , 12, 14, 15, 19, 20, 21, 23, 24, 25, 28
- , 29, 33, 37, 39, 43, 46, 51, 53, 61, 62
- , 65, 67, 68, 92, 2, 4, 10, 12, 14, 15
- , 19, 20, 21, 23, 24, 25, 28, 29, 33, 37
- , 39, 43, 46, 51, 53, 61, 62, 65, 67, 68
- , 92, 2, 4, 10, 12, 14, 15, 19, 20, 21
- , 23, 24, 25, 28, 29, 33, 37, 39, 43, 46
- , 51, 53, 61, 62, 65, 67, 68, 92, 2, 4
- , 10, 12, 14, 15, 19, 20, 21, 23, 24, 25
- , 28, 29, 33, 37, 39, 43, 46, 51, 53, 61
- , 62, 65, 67, 68, 92, 2, 4, 10, 12, 14
- , 15, 19, 20, 21, 23, 24, 25, 28, 29, 33
- , 37, 39, 43, 46, 51, 53, 61, 62, 65, 67
- , 68, 92, 2, 4, 10, 12, 14, 15, 19, 20
- , 21, 23, 24, 25, 28, 29, 33, 37, 39, 43
- , 46, 51, 53, 61, 62, 65, 67, 68, 92, 2
- , 4, 10, 12, 14, 15, 19, 20, 21, 23, 24
- , 25, 28, 29, 33, 37, 39, 43, 46, 51, 53
- , 61, 62, 65, 67, 68, 92, 2, 4, 10, 12
- , 14, 15, 19, 20, 21, 23, 24, 25, 28, 29
- , 33, 37, 39, 43, 46, 51, 53, 61, 62, 65
- , 67, 68, 92, 2, 4, 10, 12, 14, 15, 19
- , 20, 21, 23, 24, 25, 28, 29, 33, 37, 39
- , 43, 46, 51, 53, 61, 62, 65, 67, 68, 92
- , 2, 4, 10, 12, 14, 15, 19, 20, 21, 23
- , 24, 25, 28, 29, 33, 37, 39, 43, 46, 51
- , 53, 61, 62, 65, 67, 68, 92, 2, 4, 10
- , 12, 14, 15, 19, 20, 21, 23, 24, 25, 28
- , 29, 33, 37, 39, 43, 46, 51, 53, 61, 62
- , 65, 67, 68, 92, 2, 4, 10, 12, 14, 15
- , 19, 20, 21, 23, 24, 25, 28, 29, 33, 37
- , 39, 43, 46, 51, 53, 61, 62, 65, 67, 68
- , 92, 2, 4, 10, 12, 14, 15, 19, 20, 21
- , 23, 24, 25, 28, 29, 33, 37, 39, 43, 46
- , 51, 53, 61, 62, 65, 67, 68, 92, 2, 4
- , 10, 12, 14, 15, 19, 20, 21, 23, 24, 25
- , 28, 29, 33, 37, 39, 43, 46, 51, 53, 61
- , 62, 65, 67, 68, 92, 2, 4, 10, 12, 14
- , 15, 19, 20, 21, 23, 24, 25, 28, 29, 33
- , 37, 39, 43, 46, 51, 53, 61, 62, 65, 67
- , 68, 92, 2, 4, 10, 12, 14, 15, 19, 20
- , 21, 23, 24, 25, 28, 29, 33, 37, 39, 43
- , 46, 51, 53, 61, 62, 65, 67, 68, 92, 2
- , 4, 10, 12, 14, 15, 24, 25, 28, 29, 33
- , 37, 46, 51, 53, 62, 65, 67, 68, 92, 19
- , 20, 21, 19, 20, 21, 21, 33, 58, 80, 85
- , 43, 61, 21, 61, 21, 61, 25, 33, 62, 80
- , 33, 65, 67, 80, 65, 67, 80, 21, 10, 14
- , 31, 50, 80, 31, 50, 71, 80, 72, 80, 72
- , 80, 31, 51, 71, 65, 65, 80, 80, 31, 31
- , 75, 80, 80, 21, 22, 25, 21, 25, 80, 21
- , 22, 25, 43, 18, 80, 2, 4, 10, 12, 14
- , 15, 19, 20, 21, 23, 24, 25, 28, 29, 33
- , 37, 39, 43, 46, 51, 53, 61, 62, 65, 67
- , 68, 92, 2, 4, 10, 12, 14, 15, 19, 20
- , 21, 23, 24, 25, 28, 29, 33, 37, 39, 43
- , 46, 51, 53, 61, 62, 65, 67, 68, 92, 2
- , 4, 10, 12, 14, 15, 19, 20, 21, 23, 24
- , 25, 28, 29, 33, 37, 39, 43, 46, 51, 53
- , 61, 62, 65, 67, 68, 92, 19, 21, 39, 19
- , 21, 39, 19, 21, 39, 19, 21, 39, 19, 21
- , 39, 19, 21, 39, 19, 21, 39, 75, 80, 26
- , 27, 42, 43, 45, 54, 63, 96, 71, 80, 26
- , 27, 42, 43, 45, 54, 63, 96, 26, 27, 42
- , 45, 54, 26, 27, 42, 43, 45, 54, 63, 96
- , 26, 27, 42, 43, 45, 54, 63, 96, 26, 27
- , 42, 45, 54, 63, 75, 80, 75, 80, 26, 27
- , 42, 43, 45, 54, 60, 63, 72, 77, 84, 85
- , 84, 85, 21, 61, 80, 26, 42, 45, 26, 42
- , 45, 59, 63, 65, 26, 42, 45, 59, 63, 65
- , 80, 80, 71, 77, 80, 72, 75, 72, 75, 72
- , 75, 85, 72, 75, 10, 21, 25, 26, 27, 42
- , 43, 44, 45, 55, 56, 59, 60, 65, 10, 21
- , 25, 26, 27, 42, 43, 44, 45, 55, 56, 59
- , 60, 65, 10, 21, 25, 26, 27, 42, 43, 44
- , 45, 55, 56, 59, 60, 65, 10, 21, 25, 26
- , 27, 42, 43, 44, 45, 55, 56, 59, 60, 65
- , 21, 65, 67, 68, 21, 43, 65, 67, 68, 21
- , 43, 65, 67, 68, 72, 75, 84, 85, 21, 61
- , 26, 27, 42, 45, 54, 60, 63) ;
- --| Map of states to sets of follow symbols
- -- NYU Reference Name: FOLLOW
-
- ------------------------------------------------------------------
- -- Action_Token_Map
- ------------------------------------------------------------------
-
-
- type Action_Token_Array_Index is array(
- PositiveParserInteger range <>) of GC.ParserInteger ;
- --| For indexing the All Action Token Array.
- --| Maps a given state into the lower and upper bounds of a slice
- --| of the All Action Index Array.
-
- Action_Token_MapIndex : constant Action_Token_Array_Index :=
- ( 1, 1, 2, 2, 3, 2, 3, 9, 10, 11
- , 12, 11, 12, 16, 17, 17, 18, 17, 18, 17
- , 18, 17, 18, 28, 29, 28, 29, 30, 31, 30
- , 31, 32, 33, 33, 34, 34, 35, 34, 35, 34
- , 35, 34, 35, 34, 35, 34, 35, 34, 35, 36
- , 37, 37, 38, 38, 39, 39, 40, 39, 40, 39
- , 40, 40, 41, 43, 44, 44, 45, 44, 45, 44
- , 45, 45, 46, 45, 46, 45, 46, 73, 74, 73
- , 74, 73, 74, 73, 74, 85, 86, 85, 86, 85
- , 86, 86, 87, 86, 87, 95, 96, 99, 100, 99
- , 100, 99, 100, 99, 100, 99, 100, 100, 101, 100
- , 101, 103, 104, 104, 105, 105, 106, 106, 107, 107
- , 108, 108, 109, 111, 112, 115, 116, 115, 116, 116
- , 117, 116, 117, 123, 124, 123, 124, 123, 124, 123
- , 124, 132, 133, 132, 133, 132, 133, 132, 133, 135
- , 136, 138, 139, 139, 140, 139, 140, 139, 140, 140
- , 141, 141, 142, 142, 143, 142, 143, 142, 143, 143
- , 144, 143, 144, 143, 144, 145, 146, 146, 147, 146
- , 147, 146, 147, 147, 148, 147, 148, 147, 148, 148
- , 149, 149, 150, 149, 150, 150, 151, 150, 151, 152
- , 153, 154, 155, 155, 156, 155, 156, 157, 158, 173
- , 174, 177, 178, 177, 178, 178, 179, 179, 180, 179
- , 180, 179, 180, 180, 181, 180, 181, 181, 182, 181
- , 182, 181, 182, 181, 182, 192, 193, 192, 193, 192
- , 193, 192, 193, 192, 193, 203, 204, 214, 215, 225
- , 226, 230, 231, 241, 242, 245, 246, 245, 246, 256
- , 257, 257, 258, 269, 270, 281, 282, 292, 293, 303
- , 304, 314, 315, 325, 326, 326, 327, 327, 328, 327
- , 328, 327, 328, 327, 328, 336, 337, 336, 337, 336
- , 337, 336, 337, 336, 337, 345, 346, 345, 346, 345
- , 346, 352, 353, 355, 356, 355, 356, 355, 356, 356
- , 357, 357, 358, 358, 359, 359, 360, 361, 362, 361
- , 362, 362, 363, 362, 363, 362, 363, 363, 364, 363
- , 364, 365, 366, 366, 367, 367, 368, 377, 378, 378
- , 379, 380, 381, 381, 382, 393, 394, 395, 396, 396
- , 397, 398, 399, 398, 399, 400, 401, 401, 402, 401
- , 402, 402, 403, 402, 403, 413, 414, 414, 415, 415
- , 416, 416, 417, 427, 428, 438, 439, 438, 439, 450
- , 451, 461, 462, 461, 462, 463, 464, 463, 464, 475
- , 476, 475, 476, 476, 477, 476, 477, 476, 477, 476
- , 477, 477, 478, 477, 478, 477, 478, 478, 479, 478
- , 479, 478, 479, 478, 479, 478, 479, 478, 479, 478
- , 479, 478, 479, 479, 480, 479, 480, 479, 480, 479
- , 480, 479, 480, 479, 480, 479, 480, 479, 480, 480
- , 481, 491, 492, 499, 500, 499, 500, 510, 511, 510
- , 511, 510, 511, 510, 511, 510, 511, 510, 511, 521
- , 522, 532, 533, 532, 533, 532, 533, 532, 533, 533
- , 534, 533, 534, 534, 535, 535, 536, 535, 536, 537
- , 538, 538, 539, 539, 540, 540, 541, 541, 542, 541
- , 542, 545, 546, 546, 547, 546, 547, 549, 550, 552
- , 553, 554, 555, 555, 556, 558, 559, 559, 560, 559
- , 560, 559, 560, 559, 560, 559, 560, 559, 560, 559
- , 560, 559, 560, 559, 560, 559, 560, 559, 560, 559
- , 560, 559, 560, 560, 561, 560, 561, 560, 561, 560
- , 561, 560, 561, 560, 561, 560, 561, 560, 561, 560
- , 561, 560, 561, 560, 561, 560, 561, 560, 561, 563
- , 564, 564, 565, 565, 566, 565, 566, 565, 566, 565
- , 566, 565, 566, 565, 566, 565, 566, 565, 566, 565
- , 566, 566, 567, 569, 570, 570, 571, 571, 572, 571
- , 572, 573, 574, 576, 577, 577, 578, 577, 578, 578
- , 579, 579, 580, 579, 580, 580, 581, 581, 582, 582
- , 583, 583, 584, 584, 585, 584, 585, 584, 585, 584
- , 585, 584, 585, 584, 585, 584, 585, 584, 585, 584
- , 585, 584, 585, 584, 585, 595, 596, 606, 607, 606
- , 607, 606, 607, 606, 607, 618, 619, 618, 619, 629
- , 630, 640, 641, 640, 641, 641, 642, 641, 642, 641
- , 642, 641, 642, 641, 642, 641, 642, 641, 642, 644
- , 645, 646, 647, 647, 648, 647, 648, 649, 650, 657
- , 658, 658, 659, 662, 663, 663, 664, 664, 665, 665
- , 666, 666, 667, 668, 669, 669, 670, 670, 671, 670
- , 671, 671, 672, 671, 672, 682, 683, 683, 684, 683
- , 684, 684, 685, 687, 688, 688, 689, 689, 690, 690
- , 691, 691, 692, 692, 693, 693, 694, 696, 697, 700
- , 701, 701, 702, 707, 708, 708, 709, 710, 711, 713
- , 714, 714, 715, 714, 715, 735, 736, 737, 738, 737
- , 738, 748, 749, 748, 749, 748, 749, 759, 760, 760
- , 761, 761, 762, 761, 762, 761, 762, 761, 762, 772
- , 773, 774, 775, 774, 775, 775, 776, 776, 777, 776
- , 777, 776, 777, 777, 778, 777, 778, 777, 778, 777
- , 778, 788, 789, 788, 789, 788, 789, 789, 790, 790
- , 791, 791, 792, 792, 793, 793, 794, 794, 795, 795
- , 796, 796, 797, 796, 797, 797, 798, 798, 799, 798
- , 799, 798, 799, 798, 799, 798, 799, 799, 800, 800
- , 801, 800, 801, 800, 801, 803, 804, 803, 804, 803
- , 804, 803, 804, 814, 815, 815, 816, 815, 816, 816
- , 817, 816, 817, 841, 842, 866, 867, 866, 867, 866
- , 867, 866, 867, 867, 868, 867, 868, 867, 868, 870
- , 871, 874, 875, 885, 886, 886, 887, 887, 888, 888
- , 889, 889, 890, 889, 890, 899, 900, 900, 901, 900
- , 901, 901, 902, 904, 905, 906, 907, 907, 908, 908
- , 909, 913, 914, 913, 914, 913, 914, 913, 914, 913
- , 914, 913, 914, 913, 914, 913, 914, 913, 914, 915
- , 916, 916, 917, 920, 921, 921, 922, 924, 925, 925
- , 926, 936, 937, 947, 948, 950, 951, 951, 952, 962
- , 963, 963, 964, 965, 966, 977, 978, 977, 978, 978
- , 979, 979, 980, 979, 980, 984, 985, 984, 985, 984
- , 985, 984, 985, 1004, 1005, 1004, 1005, 1004, 1005, 1004
- , 1005, 1004, 1005, 1004, 1005, 1004, 1005, 1004, 1005, 1004
- , 1005, 1004, 1005, 1004, 1005, 1004, 1005, 1004, 1005, 1004
- , 1005, 1004, 1005, 1004, 1005, 1004, 1005, 1004, 1005, 1007
- , 1008, 1009, 1010, 1009, 1010, 1009, 1010, 1009, 1010, 1009
- , 1010, 1009, 1010, 1009, 1010, 1010, 1011, 1010, 1011, 1011
- , 1012, 1012, 1013, 1012, 1013, 1012, 1013, 1012, 1013, 1012
- , 1013, 1012, 1013, 1013, 1014, 1013, 1014, 1013, 1014, 1017
- , 1018, 1028, 1029, 1029, 1030, 1029, 1030, 1029, 1030, 1029
- , 1030, 1029, 1030, 1030, 1031, 1030, 1031, 1031, 1032, 1033
- , 1034, 1033, 1034, 1033, 1034, 1034, 1035, 1036, 1037, 1047
- , 1048, 1058, 1059, 1059, 1060, 1071, 1072, 1072, 1073, 1073
- , 1074, 1075, 1076, 1076, 1077, 1077, 1078, 1077, 1078, 1078
- , 1079, 1079, 1080, 1090, 1091, 1101, 1102, 1102, 1103, 1103
- , 1104, 1104, 1105, 1105, 1106, 1107, 1108, 1108, 1109, 1108
- , 1109, 1108, 1109, 1108, 1109, 1108, 1109, 1108, 1109, 1108
- , 1109, 1108, 1109, 1108, 1109, 1108, 1109, 1108, 1109, 1109
- , 1110, 1110, 1111, 1110, 1111, 1121, 1122, 1132, 1133, 1133
- , 1134, 1134, 1135, 1135, 1136, 1135, 1136, 1136, 1137, 1137
- , 1138, 1140, 1141, 1151, 1152, 1151, 1152, 1151, 1152, 1151
- , 1152, 1151, 1152, 1152, 1153, 1152, 1153, 1152, 1153, 1152
- , 1153, 1155, 1156, 1156, 1157, 1157, 1158, 1158, 1159, 1169
- , 1170, 1169, 1170, 1172, 1173, 1174, 1175, 1174, 1175, 1174
- , 1175, 1175, 1176, 1175, 1176, 1175, 1176, 1177, 1178, 1177
- , 1178, 1178, 1179, 1186, 1187, 1186, 1187, 1191, 1192, 1192
- , 1193, 1197, 1198, 1197, 1198, 1208, 1209, 1209, 1210, 1235
- , 1236, 1235, 1236, 1235, 1236, 1235, 1236, 1236, 1237, 1236
- , 1237, 1247, 1248, 1248, 1249, 1248, 1249, 1249, 1250, 1251
- , 1252, 1252, 1253, 1254, 1255, 1254, 1255, 1255, 1256, 1256
- , 1257, 1258, 1259, 1258, 1259, 1258, 1259, 1262, 1263, 1262
- , 1263, 1262, 1263, 1263, 1264, 1263, 1264, 1264, 1265, 1265
- , 1266, 1266, 1267, 1266, 1267, 1267, 1268, 1278, 1279, 1278
- , 1279, 1279, 1280, 1280, 1281, 1281, 1282, 1285, 1286, 1285
- , 1286, 1286, 1287, 1286, 1287, 1286, 1287, 1286, 1287, 1286
- , 1287, 1287, 1288, 1288, 1289, 1289, 1290, 1290, 1291, 1292
- , 1293, 1292, 1293, 1292, 1293, 1292, 1293, 1293, 1294, 1293
- , 1294, 1293, 1294, 1294, 1295, 1295, 1296, 1296, 1297, 1296
- , 1297, 1296, 1297, 1296, 1297, 1296, 1297, 1296, 1297, 1296
- , 1297, 1296, 1297, 1296, 1297, 1298, 1299, 1302, 1303, 1303
- , 1304, 1304, 1305, 1305, 1306, 1307, 1308, 1307, 1308, 1307
- , 1308, 1311, 1312, 1312, 1313, 1314, 1315, 1325, 1326, 1327
- , 1328, 1327, 1328, 1327, 1328, 1328, 1329, 1339, 1340, 1339
- , 1340, 1339, 1340, 1341, 1342, 1341, 1342, 1341, 1342, 1341
- , 1342, 1342, 1343, 1353, 1354, 1357, 1358, 1357, 1358, 1357
- , 1358, 1357, 1358, 1357, 1358, 1357, 1358, 1357, 1358, 1357
- , 1358, 1359, 1360, 1359, 1360, 1360, 1361, 1361, 1362, 1361
- , 1362, 1362, 1363, 1363, 1364, 1363, 1364, 1363, 1364, 1364
- , 1365, 1365, 1366, 1367, 1368, 1367, 1368, 1367, 1368, 1368
- , 1369, 1368, 1369, 1369, 1370, 1369, 1370, 1370, 1371, 1372
- , 1373, 1384, 1385, 1384, 1385, 1386, 1387, 1386, 1387, 1386
- , 1387, 1394, 1395, 1394, 1395, 1394, 1395, 1394, 1395, 1394
- , 1395, 1405, 1406, 1406, 1407, 1410, 1411, 1410, 1411, 1414
- , 1415, 1414, 1415, 1415, 1416, 1417, 1418, 1418, 1419, 1419
- , 1420, 1419, 1420, 1420, 1421, 1420, 1421, 1420, 1421, 1421
- , 1422, 1423, 1424, 1425, 1426, 1427, 1428, 1427, 1428, 1427
- , 1428, 1427, 1428, 1427, 1428, 1427, 1428, 1427, 1428, 1430
- , 1431, 1430, 1431, 1457, 1458, 1458, 1459, 1458, 1459, 1458
- , 1459, 1458, 1459, 1460, 1461, 1460, 1461, 1461, 1462, 1461
- , 1462, 1472, 1473, 1473, 1474, 1473, 1474, 1473, 1474, 1474
- , 1475, 1498, 1499, 1498, 1499, 1498, 1499, 1500, 1501, 1500
- , 1501, 1500, 1501, 1501, 1502, 1501, 1502, 1501, 1502, 1502
- , 1503, 1514, 1515, 1515, 1516, 1516, 1517, 1517, 1518, 1517
- , 1518, 1517, 1518, 1518, 1519, 1518, 1519, 1518, 1519, 1518
- , 1519, 1518, 1519, 1519, 1520, 1522, 1523, 1522, 1523, 1522
- , 1523, 1533, 1534, 1534, 1535, 1535, 1536, 1536, 1537, 1547
- , 1548, 1548, 1549, 1549, 1550, 1549, 1550, 1550, 1551, 1561
- , 1562, 1562, 1563, 1562, 1563, 1563, 1564, 1564, 1565, 1564
- , 1565, 1565, 1566, 1566, 1567, 1566, 1567, 1566, 1567, 1566
- , 1567, 1568, 1569, 1578, 1579, 1578, 1579, 1581, 1582, 1582
- , 1583, 1584, 1585, 1585, 1586, 1597, 1598, 1597, 1598, 1597
- , 1598, 1597, 1598, 1598, 1599, 1599, 1600, 1600, 1601, 1603
- , 1604, 1603, 1604, 1603, 1604, 1608, 1609, 1608, 1609, 1609
- , 1610, 1620, 1621, 1620, 1621, 1621, 1622, 1622, 1623, 1622
- , 1623, 1624, 1625, 1625, 1626, 1625, 1626, 1629, 1630, 1629
- , 1630, 1629, 1630, 1629, 1630, 1629, 1630, 1630, 1631, 1631
- , 1632, 1631, 1632, 1632, 1633, 1632, 1633, 1632, 1633, 1633
- , 1634, 1634, 1635, 1639, 1640, 1640, 1641, 1640, 1641, 1641
- , 1642, 1642, 1643, 1643, 1644, 1644, 1645, 1644, 1645, 1645
- , 1646, 1646, 1647, 1646, 1647, 1648, 1649, 1648, 1649, 1649
- , 1650, 1649, 1650, 1650, 1651, 1652, 1653, 1653, 1654, 1653
- , 1654, 1654, 1655, 1655, 1656, 1657, 1658, 1657, 1658, 1657
- , 1658, 1658, 1659, 1659, 1660, 1659, 1660, 1660, 1661, 1662
- , 1663, 1662, 1663, 1663, 1664, 1664, 1665, 1664, 1665, 1664
- , 1665, 1664, 1665, 1665, 1666, 1665, 1666, 1667, 1668, 1668
- , 1669, 1668, 1669, 1668, 1669, 1668, 1669, 1669, 1670, 1670
- , 1671, 1670, 1671, 1670, 1671, 1671, 1672, 1671, 1672, 1671
- , 1672, 1671, 1672, 1672, 1673, 1672, 1673, 1674, 1675, 1675
- , 1676, 1675, 1676, 1677, 1678, 1677, 1678, 1677, 1678, 1677
- , 1678, 1678, 1679, 1679, 1680, 1680, 1681, 1680, 1681, 1680
- , 1681, 1692, 1693, 1692, 1693, 1692, 1693, 1692, 1693, 1692
- , 1693, 1692, 1693, 1692, 1693, 1692, 1693, 1693, 1694, 1695
- , 1696, 1696, 1697, 1696, 1697, 1698, 1699, 1698, 1699, 1698
- , 1699, 1699, 1700, 1701, 1702, 1702, 1703, 1702, 1703, 1702
- , 1703, 1703, 1704, 1704, 1705, 1704, 1705, 1704) ;
-
- Action_Token_Map : constant Action_Token_Array :=
- ( 43, 65, 27, 43, 45, 54, 63, 26, 42, 71
- , 80, 45, 26, 27, 42, 54, 63, 35, 37, 66
- , 67, 3, 36, 65, 68, 71, 74, 76, 65, 67
- , 11, 65, 65, 71, 80, 31, 80, 31, 31, 80
- , 26, 42, 45, 65, 65, 7, 30, 34, 36, 39
- , 47, 49, 69, 70, 72, 73, 74, 77, 78, 81
- , 82, 83, 85, 86, 87, 89, 90, 91, 64, 71
- , 75, 76, 84, 76, 3, 35, 36, 37, 40, 65
- , 66, 67, 68, 71, 74, 72, 30, 81, 82, 83
- , 90, 36, 86, 89, 91, 47, 70, 71, 77, 75
- , 64, 7, 39, 7, 39, 64, 7, 39, 69, 74
- , 76, 34, 49, 73, 78, 87, 35, 37, 65, 66
- , 68, 67, 71, 3, 35, 36, 66, 67, 68, 71
- , 37, 65, 31, 71, 51, 59, 63, 65, 65, 71
- , 65, 35, 35, 65, 67, 65, 31, 43, 60, 71
- , 70, 77, 84, 85, 85, 72, 75, 36, 81, 82
- , 83, 85, 86, 90, 7, 30, 39, 64, 72, 75
- , 84, 89, 91, 77, 47, 70, 71, 72, 75, 80
- , 30, 3, 35, 36, 37, 68, 76, 65, 66, 67
- , 71, 74, 35, 36, 37, 65, 66, 68, 74, 76
- , 3, 67, 71, 3, 37, 65, 66, 68, 71, 74
- , 35, 36, 67, 76, 36, 37, 66, 67, 68, 71
- , 74, 76, 3, 35, 65, 16, 17, 47, 65, 71
- , 3, 68, 71, 76, 35, 36, 37, 65, 66, 67
- , 74, 6, 65, 67, 68, 3, 36, 37, 65, 66
- , 67, 68, 71, 74, 76, 35, 75, 3, 36, 37
- , 58, 65, 66, 35, 67, 68, 71, 74, 76, 35
- , 37, 66, 67, 68, 71, 74, 76, 3, 19, 36
- , 65, 3, 36, 66, 67, 68, 74, 76, 35, 37
- , 65, 71, 3, 35, 36, 65, 67, 71, 74, 76
- , 37, 66, 68, 3, 35, 36, 37, 65, 66, 68
- , 71, 74, 76, 67, 3, 36, 37, 74, 76, 35
- , 65, 66, 67, 68, 71, 58, 19, 3, 35, 36
- , 65, 66, 67, 68, 71, 37, 3, 35, 36, 37
- , 65, 66, 67, 68, 71, 35, 66, 67, 68, 37
- , 65, 71, 77, 70, 71, 35, 65, 65, 65, 26
- , 45, 79, 65, 72, 77, 65, 43, 25, 26, 27
- , 42, 55, 56, 59, 60, 45, 65, 10, 65, 67
- , 65, 44, 45, 65, 21, 25, 26, 27, 42, 55
- , 56, 59, 60, 10, 21, 65, 51, 71, 75, 80
- , 65, 65, 35, 36, 37, 65, 66, 67, 68, 71
- , 74, 76, 3, 71, 65, 65, 3, 36, 37, 65
- , 66, 35, 67, 68, 71, 74, 76, 3, 35, 36
- , 65, 66, 68, 71, 37, 67, 74, 76, 3, 35
- , 36, 66, 76, 37, 40, 65, 67, 68, 71, 74
- , 3, 35, 36, 37, 65, 76, 66, 67, 68, 71
- , 74, 84, 85, 3, 36, 37, 40, 65, 66, 71
- , 74, 76, 35, 67, 68, 75, 86, 86, 72, 65
- , 35, 36, 65, 71, 74, 3, 37, 66, 67, 68
- , 76, 81, 83, 90, 91, 30, 36, 82, 89, 67
- , 68, 66, 71, 74, 76, 3, 35, 36, 37, 65
- , 36, 37, 66, 67, 74, 76, 3, 35, 65, 68
- , 71, 3, 65, 67, 68, 71, 74, 76, 35, 36
- , 37, 66, 65, 77, 79, 31, 71, 31, 75, 30
- , 65, 26, 42, 45, 56, 65, 77, 71, 80, 65
- , 68, 67, 65, 11, 65, 11, 59, 65, 65, 79
- , 31, 50, 80, 31, 80, 80, 71, 77, 80, 65
- , 65, 59, 65, 31, 50, 80, 65, 80, 65, 80
- , 71, 77, 43, 72, 35, 36, 37, 66, 3, 65
- , 67, 68, 71, 74, 76, 3, 65, 66, 67, 71
- , 74, 76, 35, 36, 37, 68, 35, 36, 37, 40
- , 65, 3, 66, 67, 68, 71, 74, 76, 3, 65
- , 74, 76, 35, 36, 37, 66, 67, 68, 71, 3
- , 35, 36, 37, 65, 67, 71, 74, 66, 68, 76
- , 75, 71, 77, 80, 30, 41, 65, 72, 80, 5
- , 8, 17, 32, 44, 71, 16, 47, 65, 65, 67
- , 68, 94, 80, 65, 41, 88, 72, 80, 11, 11
- , 31, 3, 35, 36, 37, 65, 76, 66, 67, 68
- , 71, 74, 65, 60, 77, 70, 71, 60, 50, 31
- , 65, 65, 31, 71, 31, 80, 8, 23, 13, 65
- , 43, 45, 26, 27, 42, 56, 60, 43, 54, 35
- , 68, 65, 67, 54, 2, 4, 12, 14, 28, 29
- , 43, 46, 51, 53, 62, 68, 10, 15, 24, 25
- , 33, 37, 65, 67, 92, 23, 21, 37, 65, 66
- , 67, 76, 3, 35, 36, 68, 71, 74, 42, 45
- , 56, 21, 25, 26, 27, 55, 59, 60, 65, 35
- , 80, 37, 65, 66, 67, 76, 3, 35, 36, 68
- , 71, 74, 75, 80, 75, 86, 75, 35, 36, 37
- , 65, 66, 67, 68, 71, 74, 3, 76, 88, 51
- , 65, 65, 71, 94, 94, 44, 94, 94, 80, 79
- , 70, 71, 77, 76, 3, 35, 36, 37, 65, 66
- , 67, 68, 71, 74, 80, 65, 7, 64, 69, 70
- , 71, 72, 73, 74, 75, 76, 77, 78, 81, 82
- , 83, 85, 87, 30, 34, 36, 39, 49, 89, 90
- , 91, 30, 34, 36, 39, 49, 69, 70, 72, 76
- , 82, 83, 85, 87, 89, 90, 91, 7, 64, 71
- , 73, 74, 75, 77, 78, 81, 85, 9, 48, 71
- , 16, 17, 65, 47, 37, 65, 66, 68, 71, 74
- , 76, 3, 35, 36, 67, 65, 65, 31, 31, 16
- , 35, 44, 71, 5, 8, 17, 32, 47, 48, 65
- , 71, 8, 65, 88, 50, 80, 88, 88, 16, 17
- , 47, 71, 50, 31, 80, 80, 77, 70, 71, 80
- , 80, 65, 67, 68, 65, 68, 76, 3, 35, 36
- , 37, 65, 66, 67, 71, 74, 3, 35, 36, 68
- , 74, 76, 37, 65, 66, 67, 71, 61, 65, 80
- , 65, 3, 35, 36, 37, 65, 66, 67, 68, 71
- , 74, 76, 80, 65, 80, 36, 37, 65, 66, 71
- , 80, 3, 35, 67, 68, 74, 76, 79, 65, 77
- , 70, 71, 80, 88, 2, 10, 12, 14, 24, 25
- , 28, 29, 33, 37, 65, 67, 68, 92, 4, 15
- , 46, 51, 53, 62, 62, 25, 33, 10, 14, 65
- , 72, 65, 65, 71, 16, 17, 47, 3, 35, 37
- , 65, 67, 68, 36, 66, 71, 74, 76, 38, 72
- , 65, 72, 80, 31, 72, 75, 68, 3, 35, 36
- , 37, 65, 66, 67, 71, 74, 76, 3, 35, 65
- , 66, 68, 71, 74, 76, 36, 37, 67, 9, 35
- , 36, 37, 40, 67, 68, 71, 74, 76, 3, 65
- , 66, 80, 80, 77, 80, 80, 54, 43, 22, 3
- , 36, 37, 35, 65, 66, 67, 68, 71, 74, 76
- , 35, 36, 66, 67, 68, 71, 3, 37, 65, 74
- , 76, 44, 65, 80, 37, 65, 68, 80, 47, 47
- , 36, 37, 65, 66, 67, 68, 71, 76, 3, 35
- , 74, 67, 68, 71, 76, 3, 65, 66, 74, 35
- , 36, 37, 88, 88, 65, 80, 80, 65, 67, 68
- , 65, 66, 68, 71, 76, 3, 35, 36, 37, 67
- , 74, 43, 70, 71, 77, 71, 31, 80, 3, 36
- , 37, 66, 68, 74, 35, 65, 67, 71, 76, 61
- , 77, 80, 77, 80, 58, 77, 80, 80, 4, 15
- , 61, 65, 43, 57, 67, 68, 14, 10, 25, 33
- , 62, 93, 16, 17, 47, 65, 71, 3, 35, 36
- , 65, 67, 71, 74, 37, 66, 68, 76, 43, 2
- , 4, 12, 14, 15, 28, 29, 51, 53, 61, 62
- , 65, 67, 68, 10, 19, 20, 21, 23, 24, 25
- , 33, 37, 39, 46, 92, 65, 71, 76, 3, 35
- , 36, 37, 65, 66, 67, 68, 74, 33, 65, 61
- , 43, 21, 72, 75, 80, 77, 72, 75, 47, 70
- , 71, 77, 65, 88, 31, 65, 80, 65, 66, 67
- , 68, 71, 74, 3, 35, 36, 37, 76, 80, 34
- , 43, 65, 67, 68, 21, 75, 80, 65, 22, 65
- , 21, 25, 80, 80, 21, 43, 72, 80, 70, 71
- , 47, 77, 80, 80, 80, 77, 80, 70, 71, 77
- , 80, 72, 75, 80, 65, 67, 68, 71, 74, 76
- , 3, 35, 36, 37, 66, 18, 80, 80, 37, 67
- , 68, 74, 76, 3, 35, 36, 65, 66, 71, 19
- , 20, 80, 3, 35, 36, 37, 74, 65, 66, 67
- , 68, 71, 76, 70, 71, 77, 80, 39, 19, 80
- , 80, 30, 21, 65, 80, 65, 40, 61, 80, 80
- , 72, 75, 35, 37, 65, 71, 74, 76, 3, 36
- , 66, 67, 68, 94, 75, 72, 8, 16, 17, 32
- , 44, 47, 71, 5, 3, 36, 65, 66, 74, 76
- , 35, 37, 67, 68, 71, 48, 70, 71, 9, 77
- , 21, 65, 67, 68, 80, 21, 25, 71, 65, 43
- , 48, 12, 65, 75, 72, 31, 80, 65, 67, 68
- , 7, 34, 36, 39, 47, 49, 64, 69, 71, 73
- , 74, 75, 76, 77, 81, 82, 83, 86, 87, 89
- , 90, 91, 30, 70, 72, 78, 79, 72, 61, 43
- , 80, 35, 36, 66, 67, 76, 3, 37, 65, 68
- , 71, 74, 21, 85, 68, 28, 29, 37, 39, 43
- , 46, 51, 53, 62, 65, 67, 92, 2, 4, 10
- , 12, 14, 15, 19, 21, 24, 25, 33, 19, 39
- , 21, 43, 35, 37, 65, 66, 67, 68, 71, 74
- , 76, 3, 36, 52, 33, 21, 80, 77, 38, 65
- , 67, 68, 3, 65, 67, 68, 71, 74, 35, 36
- , 37, 66, 76, 80, 80, 80, 3, 36, 37, 65
- , 68, 71, 74, 35, 66, 67, 76, 43, 48, 65
- , 36, 37, 65, 66, 67, 68, 71, 74, 3, 35
- , 76, 80, 43, 43, 65, 79, 65, 68, 16, 17
- , 32, 71, 5, 8, 35, 44, 47, 48, 70, 77
- , 71, 71, 72, 80, 21, 3, 36, 40, 65, 71
- , 74, 35, 37, 66, 67, 68, 76, 58, 29, 43
- , 4, 15, 57, 4, 15, 43, 57, 61, 53, 3
- , 35, 36, 37, 68, 71, 65, 66, 67, 74, 76
- , 65, 33, 85, 84, 65, 70, 71, 77, 47, 47
- , 80, 72, 31, 65, 12, 21, 43, 61, 65, 43
- , 44, 80, 80, 65, 65, 85, 21, 61, 80, 21
- , 15, 43, 80, 80, 65, 40, 65, 94, 80, 71
- , 72, 80, 88, 80, 80, 84, 85, 12, 53, 21
- , 80, 65, 43, 61, 80, 72, 80, 80, 80, 53
- , 36, 37, 40, 65, 66, 67, 71, 76, 3, 35
- , 68, 74, 80, 72, 80, 85, 61, 21, 37, 85
- , 84, 12, 37, 80) ;
- --| Action_Token_Map is an array that
- --| maps from each state (using action map) to a set of
- --| action tokens. An action token is a terminal symbol
- --| (except EOF_Token) for which in the given state an
- --| explicit (non-default) shift or reduce action
- --| is defined.
- --| Used to cut reduce the
- --| number of primary recovery candidates.
-
- ------------------------------------------------------------------
- -- Shift_State_Map
- ------------------------------------------------------------------
-
- type Shift_State_Index_Array is array(
- PositiveParserInteger range <>) of GC.ParserInteger;
- --| For indexing the All Action Token Array.
- --| Maps a given state into the lower and upper bounds of a slice
- --| of the All Action Index Array.
-
- Shift_State_MapIndex : constant Shift_State_Index_Array :=
- ( 1, 1, 2, 2, 3, 3, 4, 4, 5, 5
- , 6, 6, 7, 9, 10, 11, 12, 14, 15, 15
- , 16, 18, 19, 22, 23, 23, 24, 24, 25, 25
- , 26, 28, 29, 31, 32, 32, 33, 36, 37, 37
- , 38, 56, 57, 57, 58, 59, 60, 60, 61, 62
- , 63, 64, 65, 65, 66, 66, 67, 68, 69, 72
- , 73, 93, 94, 96, 97, 100, 101, 102, 103, 107
- , 108, 109, 110, 112, 113, 114, 115, 119, 120, 123
- , 124, 125, 126, 130, 131, 132, 133, 139, 140, 140
- , 141, 141, 142, 146, 147, 151, 152, 152, 153, 156
- , 157, 159, 160, 160, 161, 164, 165, 168, 169, 169
- , 170, 172, 173, 173, 174, 177, 178, 180, 181, 183
- , 184, 189, 190, 190, 191, 192, 193, 194, 195, 231
- , 232, 232, 233, 237, 238, 240, 241, 241, 242, 245
- , 246, 268, 269, 293, 294, 294, 295, 296, 297, 309
- , 310, 311, 312, 315, 316, 316, 317, 322, 323, 408
- , 409, 409, 410, 410, 411, 411, 412, 414, 415, 424
- , 425, 428, 429, 429, 430, 432, 433, 433, 434, 434
- , 435, 435, 436, 436, 437, 437, 438, 443, 444, 443
- , 444, 443, 444, 443, 444, 444, 445, 446, 447, 451
- , 452, 455, 456, 456, 457, 457, 458, 458, 459, 459
- , 460, 460, 461, 463, 464, 466, 467, 468, 469, 471
- , 472, 472, 473, 475, 476, 476, 477, 481, 482, 489
- , 490, 497, 498, 500, 501, 516, 517, 517, 518, 518
- , 519, 519, 520, 520, 521, 522, 523, 525, 526, 527
- , 528, 528, 529, 529, 530, 530, 531, 532, 533, 533
- , 534, 535, 536, 536, 537, 544, 545, 545, 546, 546
- , 547, 553, 554, 555, 556, 557, 558, 575, 576, 577
- , 578, 578, 579, 579, 580, 580, 581, 582, 583, 583
- , 584, 584, 585, 586, 587, 587, 588, 588, 589, 603
- , 604, 608, 609, 609, 610, 611, 612, 614, 615, 629
- , 630, 630, 631, 631, 632, 632, 633, 633, 634, 635
- , 636, 636, 637, 640, 641, 643, 644, 646, 647, 648
- , 649, 650, 651, 651, 652, 652, 653, 654, 655, 657
- , 658, 658, 659, 660, 661, 661, 662, 663, 664, 665
- , 666, 666, 667, 667, 668, 668, 669, 670, 671, 671
- , 672, 672, 673, 673, 674, 678, 679, 679, 680, 683
- , 684, 687, 688, 690, 691, 693, 694, 694, 695, 697
- , 698, 699, 700, 710, 711, 711, 712, 712, 713, 713
- , 714, 714, 715, 715, 716, 716, 717, 717, 718, 718
- , 719, 719, 720, 722, 723, 725, 726, 726, 727, 728
- , 729, 729, 730, 732, 733, 733, 734, 734, 735, 735
- , 736, 736, 737, 737, 738, 738, 739, 739, 740, 749
- , 750, 757, 758, 759, 760, 760, 761, 772, 773, 774
- , 775, 776, 777, 777, 778, 778, 779, 779, 780, 780
- , 781, 781, 782, 782, 783, 784, 785, 785, 786, 786
- , 787, 787, 788, 789, 790, 790, 791, 791, 792, 792
- , 793, 793, 794, 795, 796, 796, 797, 798, 799, 799
- , 800, 800, 801, 802, 803, 808, 809, 810, 811, 812
- , 813, 813, 814, 814, 815, 826, 827, 827, 828, 829
- , 830, 833, 834, 834, 835, 835, 836, 842, 843, 847
- , 848, 854, 855, 860, 861, 862, 863, 863, 864, 865
- , 866, 866, 867, 868, 869, 870, 871, 872, 873, 873
- , 874, 874, 875, 876, 877, 878, 879, 879, 880, 880
- , 881, 881, 882, 882, 883, 883, 884, 884, 885, 886
- , 887, 887, 888, 889, 890, 890, 891, 892, 893, 893
- , 894, 896, 897, 897, 898, 898, 899, 899, 900, 901
- , 902, 902, 903, 903, 904, 904, 905, 905, 906, 907
- , 908, 908, 909, 909, 910, 910, 911, 912, 913, 913
- , 914, 915, 916, 916, 917, 917, 918, 918, 919, 919
- , 920, 921, 922, 922, 923, 925, 926, 929, 930, 932
- , 933, 933, 934, 934, 935, 936, 937, 937, 938, 938
- , 939, 939, 940, 940, 941, 942, 943, 943, 944, 944
- , 945, 946, 947, 947, 948, 948, 949, 949) ;
-
- Shift_State_Map : constant Shift_State_Array :=
- ( 1, 464, 35, 465, 402, 213, 132, 135, 138, 403
- , 446, 536, 642, 805, 287, 77, 361, 425, 466, 816
- , 921, 947, 447, 618, 467, 205, 404, 547, 206, 405
- , 548, 765, 224, 231, 770, 836, 771, 293, 298, 505
- , 508, 721, 737, 745, 750, 787, 807, 809, 833, 840
- , 844, 870, 900, 904, 923, 943, 654, 448, 506, 468
- , 250, 614, 14, 88, 15, 469, 470, 875, 113, 199
- , 345, 786, 82, 85, 86, 155, 177, 340, 342, 369
- , 371, 380, 426, 439, 442, 443, 543, 544, 637, 686
- , 731, 822, 891, 406, 549, 865, 615, 714, 843, 882
- , 144, 736, 36, 167, 172, 235, 550, 37, 114, 38
- , 471, 662, 632, 847, 133, 136, 139, 781, 837, 102
- , 791, 871, 936, 398, 421, 16, 89, 251, 294, 348
- , 2, 179, 295, 407, 525, 551, 659, 866, 893, 17
- , 472, 125, 207, 408, 726, 886, 537, 552, 804, 815
- , 855, 145, 370, 438, 572, 576, 156, 473, 517, 841
- , 474, 879, 922, 934, 18, 461, 463, 651, 252, 253
- , 296, 349, 696, 221, 230, 693, 874, 158, 254, 362
- , 181, 435, 437, 590, 689, 697, 717, 828, 926, 616
- , 33, 159, 134, 137, 9, 39, 73, 78, 93, 97
- , 103, 160, 165, 208, 214, 240, 248, 289, 299, 303
- , 310, 311, 329, 352, 356, 359, 360, 363, 364, 420
- , 427, 434, 441, 475, 587, 605, 665, 711, 744, 762
- , 860, 40, 41, 74, 215, 290, 428, 42, 216, 666
- , 140, 126, 184, 436, 606, 12, 43, 81, 127, 157
- , 164, 183, 341, 353, 376, 385, 396, 409, 444, 521
- , 538, 553, 568, 577, 684, 810, 868, 912, 112, 189
- , 194, 246, 327, 387, 400, 424, 624, 633, 635, 638
- , 722, 724, 753, 759, 797, 800, 820, 825, 869, 889
- , 913, 930, 940, 146, 44, 141, 130, 190, 195, 220
- , 301, 323, 344, 511, 639, 760, 798, 801, 821, 45
- , 142, 128, 185, 247, 354, 147, 243, 336, 365, 529
- , 604, 861, 13, 83, 84, 87, 198, 302, 355, 372
- , 375, 377, 382, 384, 397, 401, 419, 445, 509, 512
- , 528, 532, 573, 583, 584, 585, 591, 597, 598, 600
- , 607, 636, 647, 648, 649, 650, 661, 669, 679, 680
- , 687, 690, 691, 694, 695, 723, 733, 735, 741, 748
- , 749, 754, 755, 756, 757, 758, 761, 766, 768, 774
- , 783, 784, 790, 795, 796, 808, 823, 830, 845, 851
- , 852, 853, 859, 888, 894, 895, 903, 906, 907, 911
- , 916, 918, 924, 929, 932, 933, 939, 949, 115, 116
- , 117, 186, 318, 883, 187, 188, 319, 535, 835, 884
- , 898, 920, 941, 946, 118, 191, 325, 326, 149, 422
- , 569, 608, 119, 120, 121, 476, 707, 417, 523, 524
- , 526, 527, 799, 3, 10, 304, 46, 212, 307, 510
- , 682, 180, 477, 718, 927, 255, 256, 257, 258, 259
- , 19, 260, 452, 20, 261, 453, 262, 454, 21, 263
- , 455, 264, 22, 265, 456, 266, 161, 238, 267, 415
- , 817, 449, 519, 542, 570, 660, 729, 885, 892, 423
- , 516, 574, 575, 676, 677, 730, 915, 410, 450, 571
- , 47, 104, 312, 313, 314, 320, 391, 429, 531, 588
- , 594, 601, 646, 675, 709, 763, 242, 268, 269, 270
- , 554, 867, 416, 567, 732, 530, 673, 555, 556, 557
- , 411, 558, 559, 412, 560, 561, 98, 236, 346, 399
- , 451, 520, 627, 634, 578, 99, 129, 192, 562, 579
- , 670, 727, 887, 563, 580, 564, 581, 48, 105, 200
- , 201, 203, 204, 222, 317, 389, 394, 395, 540, 589
- , 641, 657, 658, 803, 854, 667, 864, 752, 668, 565
- , 671, 672, 566, 413, 628, 848, 725, 522, 49, 106
- , 152, 357, 418, 462, 478, 586, 629, 674, 681, 698
- , 738, 824, 849, 630, 842, 850, 857, 880, 728, 202
- , 631, 663, 945, 948, 95, 168, 306, 366, 368, 545
- , 582, 643, 664, 747, 806, 813, 814, 862, 863, 751
- , 818, 819, 914, 928, 944, 938, 107, 390, 872, 937
- , 193, 899, 942, 169, 173, 379, 170, 174, 271, 457
- , 367, 272, 273, 746, 182, 274, 458, 459, 275, 350
- , 276, 23, 277, 24, 278, 279, 50, 51, 52, 358
- , 217, 209, 108, 53, 210, 308, 539, 708, 109, 196
- , 324, 513, 514, 110, 315, 321, 393, 197, 388, 392
- , 111, 316, 322, 54, 55, 218, 330, 131, 328, 56
- , 223, 225, 226, 227, 228, 229, 331, 332, 333, 334
- , 57, 58, 59, 60, 61, 122, 123, 62, 63, 64
- , 154, 232, 65, 153, 234, 150, 66, 233, 67, 68
- , 211, 309, 69, 70, 124, 143, 71, 148, 151, 100
- , 237, 305, 541, 592, 593, 599, 625, 678, 792, 373
- , 602, 609, 776, 785, 834, 838, 878, 479, 710, 610
- , 374, 712, 773, 777, 788, 827, 831, 877, 902, 910
- , 919, 931, 480, 611, 481, 612, 482, 483, 484, 485
- , 486, 487, 488, 699, 489, 490, 491, 492, 700, 493
- , 494, 495, 496, 497, 701, 498, 499, 613, 595, 692
- , 772, 782, 596, 688, 713, 769, 775, 832, 620, 767
- , 829, 901, 873, 500, 300, 378, 381, 623, 716, 742
- , 789, 812, 856, 881, 897, 908, 617, 288, 619, 171
- , 175, 652, 715, 621, 501, 25, 90, 241, 280, 297
- , 351, 460, 79, 80, 163, 440, 533, 239, 245, 518
- , 764, 858, 896, 925, 339, 347, 826, 890, 917, 935
- , 75, 176, 337, 244, 338, 291, 26, 91, 27, 92
- , 28, 281, 386, 282, 546, 653, 655, 743, 811, 656
- , 685, 502, 503, 504, 603, 839, 706, 702, 876, 703
- , 704, 905, 705, 778, 779, 780, 683, 4, 5, 6
- , 11, 7, 29, 30, 8, 94, 383, 178, 34, 166
- , 793, 909, 846, 719, 794, 31, 32, 76, 162, 414
- , 802, 343, 249, 292, 335, 430, 507, 515, 734, 534
- , 622, 626, 431, 432, 433, 640, 283, 284, 285, 286
- , 644, 740, 645, 739, 72, 219, 101, 720, 96) ;
- --| Shift_State_ is an array that
- --| maps from non-terminals (using shift map) to sets
- --| of states in which
- --| a shift to the non-terminal is defined.
- --| Used to determine the number of trials in primary
- --| error recovery.
-
- ------------------------------------------------------------------
- -- Subprogram Bodies Global to Package ErrorParseTables
- ------------------------------------------------------------------
-
- function Get_Action_Token_Map ( --| return the array of action tokens
- --| for the state passed in.
- In_Index : in StateRange
- --| the state to return action tokens
- --| for.
- )
- return Action_Token_Record
- is
- --| Returns
- --| This subprogram returns the action token record for the
- --| state passed in.
- Result : Action_Token_Record ;
- LowerBound, UpperBound : GC.ParserInteger ;
- --| Lower and upper bounds of the slice of Action Token Map
- begin
- LowerBound := Action_Token_MapIndex ( In_Index*2 - 1 ) ;
- UpperBound := Action_Token_MapIndex ( In_Index*2 ) ;
-
- Result.set_size := UpperBound - LowerBound + 1;
- Result.set := (others => DefaultValue) ;
- Result.set(Result.set'first .. Result.set_size) :=
- Action_Token_Map(LowerBound..UpperBound) ;
-
- return Result ;
- end Get_Action_Token_Map ;
-
- ------------------------------------------------------------------
-
- function Get_Shift_State_Map ( --| return the array of shift states
- --| for the grammar symbol passed in.
- In_Index : in GrammarSymbolRange
- --| the grammar symbol to return shifts
- --| for.
- )
- --| Raises: This subprogram raises no exceptions.
- return Shift_State_Record
- --| Returns
- --| This subprogram returns the array of shift states for the
- --| grammar symbol passed in.
- is
-
- Result : Shift_State_Record ;
- LowerBound, UpperBound : GC.ParserInteger ;
- --| Lower and upper bounds of the slice of Shift State Map
- begin
- LowerBound := Shift_State_MapIndex ( In_Index*2 - 1 ) ;
- UpperBound := Shift_State_MapIndex ( In_Index*2 ) ;
-
- Result.set_size := UpperBound - LowerBound + 1;
- Result.set := (others => DefaultValue) ;
- Result.set(Result.set'first .. Result.set_size) :=
- Shift_State_Map(LowerBound..UpperBound) ;
-
- return Result ;
- end Get_Shift_State_Map ;
-
- function Get_Grammar_Symbol ( --| return the string representation
- --| of the grammar symbol
- In_Index : in GrammarSymbolRange
- )
- return string
- is
- LowerBound, UpperBound : GC.ParserInteger ;
- --| Lower and upper bounds of the slice of Shift State Map
- begin
- LowerBound := GrammarSymbolTableIndex ( In_Index*2 - 1 ) ;
- UpperBound := GrammarSymbolTableIndex ( In_Index*2 ) ;
-
- return GrammarSymbolTable(
- Integer(LowerBound) .. Integer(UpperBound)) ;
- end Get_Grammar_Symbol ;
-
- ------------------------------------------------------------------
-
- function Get_Follow_Map ( --| return the array of follow symbols
- --| of the grammar symbol passed in
- In_Index : in FollowMapRange
- )
- -- |
- -- |Raises: This subprogram raises no exceptions.
- -- |
-
- return FollowSymbolRecord
- is
- Result : FollowSymbolRecord ;
- LowerBound, UpperBound : GC.ParserInteger ;
- Adjusted_Index : GC.ParserInteger :=
- (In_Index - FollowMapRange'first) + 1;
- begin
- LowerBound := FollowSymbolMapIndex ( Adjusted_Index*2 - 1 ) ;
- UpperBound := FollowSymbolMapIndex ( Adjusted_Index*2 ) ;
-
- Result.follow_symbol_count := UpperBound - LowerBound + 1;
- Result.follow_symbol := (others => DefaultValue) ;
- Result.follow_symbol(
- Result.follow_symbol'first ..
- Result.follow_symbol_count) :=
- FollowSymbolMap(LowerBound..UpperBound) ;
-
- return Result ;
- end Get_Follow_Map ;
-
- ------------------------------------------------------------------
-
- function GetAction ( -- see subprogram declaration
- InStateValue : in StateRange;
- InSymbolValue : in GrammarSymbolRange
- )
- return ActionRange
- is
-
- Unique : GC.ParserInteger;
- --| unique value to hash for Index.
- Index : GC.ParserInteger;
- --| into Action Tables.
- Action : GC.ParserInteger;
- --| value from Action Tables.
- CollisionCount : Natural := 0 ; --| Number of collisions.
- begin -- GetAction function
- --| Algorithm
- --|-
- --| Definitions of key objects from package ParseTables:
- --|
- --| ActionCount: the number of actions in the action tables.
- --|
- --| ActionTableOne: table of action values for all combinations of
- --| states and input actions.
- --|
- --| ActionTableTwo: hash values to check against to verify that action
- --| value at same in ActionTableOne is correct one.
- --|
- --| ActionTableSize: last in ActionTableOne and ActionTableTwo
- --| before the hash collision chains.
- --|
- --| DefaultMap: default action for each state.
- --|+
- --| The action to be returned is computed from parameters InStateValue
- --| and InSymbolValue. First, determine the unique single value:
- --|
- --| Unique := (InStateValue * GrammarSymbolCountPlusOne) +
- --| InSymbolValue;
- --|
- --| Unique is hashed by reducing modulo ActionTableSize and adding 1:
- --|
- --| Index := (Unique mod ActionTableSize) + 1;
- --|
- --| This hash value, Index, is used to ActionTableOne to
- --| obtain an Action:
- --|
- --| Action := ActionTableOne(Index);
- --|
- --| Action is then used to determine the return value:
- --|
- --| Action = 0:
- --| return DefaultMap(InStateValue);
- --|
- --| Action < ActionCount:
- --| if (Unique = ActionTableTwo(Index)) then
- --| return Action;
- --| else
- --| return DefaultMap(InStateValue);
- --| end if;
- --|
- --| Action >= ActionCount:
- --| --Search the hash collision chain
- --| Index := Action - ActionCount;
- --| while (Action /= 0) loop
- --| Index := Index + 1;
- --| Action := ActionTableTwo(Index);
- --| if (Action = Unique) then
- --| return ActionTableOne(Index);
- --| end if;
- --| end loop;
- --| return DefaultMap(InStateValue);
-
- ------------------------------------------------------------------
-
- --| The actual code used folds this algorithm into a more efficient one:
- ParserDecisionCount := Natural'succ(ParserDecisionCount) ;
-
- Unique := (InStateValue * GrammarSymbolCountPlusOne) +
- InSymbolValue;
- Index := (Unique mod ActionTableSize) + 1;
- Action := ActionTableOne(Index);
-
- if (Action >= ActionCount) then
- Index := Action - ActionCount + 1;
- while ( (ActionTableTwo(Index) /= Unique) and then
- (ActionTableTwo(Index) /= 0) ) loop
- Index := Index + 1;
- CollisionCount := Natural'succ(CollisionCount) ;
- end loop;
- Action := ActionTableOne(Index);
- end if;
-
- -- Collect statistics information.
- TotalCollisions := CollisionCount + TotalCollisions ;
- if CollisionCount > MaxCollisions then
- MaxCollisions := CollisionCount ;
- end if;
-
- if (ActionTableTwo(Index) /= Unique) then
- return DefaultMap(InStateValue);
- else
- return Action;
- end if;
-
- end GetAction; -- function
-
- function Get_LeftHandSide(
- GrammarRule : LeftHandSideRange
- ) return GrammarSymbolRange is
- begin
- return LeftHandSide(GrammarRule) ;
- end Get_LeftHandSide ;
-
- function Get_RightHandSide(
- GrammarRule : RightHandSideRange
- ) return GC.ParserInteger is
- begin
- return RightHandSide(GrammarRule) ;
- end Get_RightHandSide ;
-
- end ParseTables;
-
- ----------------------------------------------------------------------
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --REPORT.BDY
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
-
- with string_pkg; use string_pkg; -- for = and & etc.
- with compile_order_declarations; use compile_order_declarations; -- global variables
- with units_dag_pkg;
- with mini_dag_pkg;
- with nodes;
- with lookup_lists;
- with paginated_output;
- with file_manager;
- with TEXT_IO;
-
-
- package body report_pkg is
-
- ----- Package Renames -----
-
- package SP renames string_pkg;
- package COD renames compile_order_declarations;
- package PG renames Paginated_output;
- package FM renames file_manager;
- package LL renames lookup_lists;
- package WDAG renames units_dag_pkg; -- WDAG for withs_dag
- package IDAG renames mini_dag_pkg; -- IDAG for info_dag
-
- -- Local Variables --
- subtype indent_range is integer range 0..39;
- line_len : constant positive := 80;
- prev_indent : indent_range := 0;
- prev_unit : SP.string_type;
-
- -- Local Operation Specifications--
-
-
- procedure add_file_to_dag ( --| procedure which puts the file dependence
- --| info in the file_dag.
- node_label : in SP.string_type --| node to add the info for
- );
-
- --| Effects: this adds the dependencies of this file upon other files
- --| to the file_dag. It does this by looking at the file part of the
- --| node's value, creates a node for this file if there isn't one, and
- --| then looking at the file parts of the nodes withed by this one.
- --| Edges are added from the original file node to each of these files
- --| Basically this creates a dag with the labels being what was the
- --| information in the nodes of the withs_dag. It will have the same
- --| number or fewer nodes, and it will show the dependencies between
- --| files which, after all, are the things that are passed to the
- --| compiler.
-
-
-
-
-
- procedure withs_gen ( --| generates the with dependencies for
- --| the given node
- n : in SP.string_type; --| the node's label
- seen : in out COD.id_set; --| set of nodes already seen
- indent : in out indent_range; --| number of spaces to indent the output
- leaf_list : --| list of the nodes which are leaves
- in out COD.id_list_pkg.list
- );
-
- --| Effects: Recursively writes the dependencies of the branch of the graph
- --| starting at the node with the given label.
- --| It collects the leaf list for use by the report which generates the
- --| withed-by dependencies.
-
- ----------------
- Procedure withed_by_gen ( --| generates the withed-by dependencies for
- --| the given node
- n : in SP.string_type; --| the node's label
- seen : in out COD.id_set; --| set of nodes already seen
- indent : in out indent_range --| number of spaces to indent the output
- );
-
- --| Effects: Similar to those of withs_gen. It's not keeping track of leaf
- --| nodes because that's what it starts from.
-
- ----------------
-
- -- Operations --
-
-
- procedure dependency_report(--| Using the information in the DAG
- --| form and output the dependency table
- report: in form_type --| output the report in full or raw form
- ) is
- --| Overview: produce the dependency report from the dag built from the
- --| information gathered. this is done using a depth first search to
- --| produce a nested structure of dependencies in the report.
-
- roots : WDAG.roots_iter;
- seen : COD.id_set := COD.id_set_pkg.create;
- node : SP.string_type;
- leaf_list : COD.id_list_pkg.list;
- indent : indent_range := 0;
- leaves : COD.id_list_pkg.ListIter;
- leaf_node : SP.string_type;
-
- begin
-
- --| Algorithm
- --| To get the withs information:
- --| Do a depth first search
- --| and output the results indented as in the manual.
- --| To get the withed-by information:
- --| Do an upward (parents) DFS
- --| output results indented as in the manual.
-
-
- if report = full then
- -- write line (" Dependency Report: ");
- -- write line (" Withs: ");
- -- write line (" ") --newline
- PG.put_line (COD.report_file, " Dependency Report: ");
- PG.skip_line (COD.report_file);
- PG.put_line (COD.report_file, "Withs Dependencies: ");
- PG.skip_line (COD.report_file);
- PG.Set_Header (COD.report_file, 3, "Withs Dependencies: ");
- end if;
- roots := WDAG.make_roots_iter (COD.withs_dag);
- while WDAG.more (roots) loop
- WDAG.next (roots, node);
- withs_gen (node, seen, indent, leaf_list);
- PG.skip_line (COD.report_file);
- end loop;
- PG.skip_line (COD.report_file);
- PG.skip_line (COD.report_file);
- seen := COD.id_set_pkg.create;
- indent := 0;
- if report = full then
- -- write line (" Withed by dependencies: ");
- -- write line (" "); -- new line
- PG.put_line (COD.report_file, "Withed-by Dependencies: ");
- PG.skip_line (COD.report_file);
- PG.Set_Header (COD.report_file, 3, "Withed-by Dependencies: ");
- end if;
- leaves := COD.id_list_pkg.MakeListIter (leaf_list);
- while COD.id_list_pkg.more (leaves) loop
- COD.id_list_pkg.next (leaves, leaf_node);
- withed_by_gen (leaf_node, seen, indent);
- PG.skip_line (COD.report_file);
- end loop;
- --- write 3 new lines
- PG.skip_line (COD.report_file);
- PG.skip_line (COD.report_file);
- PG.skip_line (COD.report_file);
-
- end dependency_report;
- ----------------
-
-
- procedure compilation_list( --| Using the DAG form and produce
- --| the compilation order list
- report: in form_type --| output the report in full or raw form
- ) is
-
-
- --| Overview: produce the compilation lists required by report. If the
- --| file list is required build the file dag from the infomation stored
- --| in the units dag. If there were cycles created in the units dag
- --| write out the dependencies which caused the cycles ( saved in the
- --| cycles_dag).
-
- iter : WDAG.postorder_iter;
- files_iter : IDAG.postorder_iter;
- file_name : SP.string_type;
- node_label : SP.string_type;
- temp_string : SP.string_type;
- node_val : nodes.dag_node;
- file_string : SP.string_type;
- output : string (1..line_len);
- file_begin : constant := 1;
- file_end : constant := 19;
- unit_begin : constant := 21;
- unit_end : constant := 78;
-
- begin
- SP.mark;
-
- --| Algorithm
- --| If the cycles dag is not empty then
- --| write out the dependencies which caused the cycles
- --| end if
- --| -- dag package will yeild a correct ordering so let it yield one
- --| for each label value in the ordering of the dag do
- --| print the label (the unit name)
- --| if value.trouble node is true then
- --| follow the label with a '*' to indicate trouble with the
- --| ordering within the file.
- --| end if
- --| print the value.file in parentheses
- --| end for
- --| if we need the file list
- --| build the file dag from the dependency and file info in the
- --| units dag
- --| for each label in an ordering of this dag
- --| write out the label
- --| end for
- --| end if
-
- if report = full then
- -- write line (" Compilation List: ");
- -- write header on next line
- -- also set header for next page
- -- write a new line
- PG.put_line (COD.report_file, " Compilation List: ");
- PG.skip_line (COD.report_file);
- end if;
-
- if report /= files then
- if report = full then
- output := (output'range => ' ');
- output (1..9) := "File Name";
- output (20..35) := "Compilation Unit";
- PG.put_line (COD.report_file, output);
- PG.skip_line (COD.report_file);
- PG.Set_Header (COD.report_file, 3, output);
- end if;
- iter := WDAG.make_postorder_iter (COD.withs_dag);
- while WDAG.more (iter) loop
- WDAG.next (iter, node_label, node_val);
- temp_string := node_val.name;
- if SP.length (temp_string) > (unit_end - unit_begin) + 1 then
- temp_string := SP.substr (temp_string,
- 1,
- (unit_end - unit_begin) + 1);
- end if;
- if node_val.trouble_node then
- temp_string := SP."&" (temp_string, " *");
- end if;
- if SP.equal ( node_val.file, "") then
- begin
- file_string := SP."&" ("# ",
- FM.strip_dir (LL.lookup (node_label)));
- exception
- when LL.not_found =>
- file_string := SP.create ("(not found)");
- end;
- else
- file_string := FM.strip_dir (node_val.file);
- if SP.length (file_string) > file_end then
- file_string := SP.substr (file_string, 1, file_end);
- end if;
- end if;
-
- output := (output'range => ' ');
- output (file_begin..SP.length (file_string)) :=
- SP.value (file_string);
- output (unit_begin..SP.length(temp_string)+(unit_begin-1)) :=
- SP.value (temp_string);
- PG.put_line (COD.report_file, output);
-
- end loop;
- PG.skip_line (COD.report_file);
- PG.skip_line (COD.report_file);
- end if;
- if report /= units then
- if report = full then
- PG.skip_line (COD.report_file);
- PG.put_line (COD.report_file, "File Order: ");
- PG.skip_line (COD.report_file);
- PG.Set_Header (COD.report_file, 3, "File Order: ");
- end if;
- files_iter := IDAG.make_postorder_iter (COD.files_dag);
- while IDAG.more(files_iter) loop
- IDAG.next (files_iter, file_name);
- PG.put_line (COD.report_file, file_name);
- end loop;
- end if;
- PG.Skip_Line (COD.report_file);
- PG.Skip_Line (COD.report_file);
- SP.release;
-
- end compilation_list;
-
- --------------------
-
- procedure report_cycles --| Report any cycles found in the units given
- is
-
- e_iter : IDAG.edges_iter;
- from : SP.string_type;
- to : SP.string_type;
- temp_string : SP.string_type;
- n_iter : WDAG.nodes_iter;
- node_label : SP.string_type;
-
- begin
- SP.mark;
-
- n_iter := WDAG.make_nodes_iter (COD.withs_dag);
- while WDAG.more (n_iter) loop
- WDAG.next (n_iter, node_label);
- add_file_to_dag (node_label);
- end loop;
-
- if not IDAG.is_empty (COD.cycle_dag) then
- e_iter := IDAG.make_edges_iter (COD.cycle_dag);
- PG.put_line (COD.report_file,
- "The reports following do not reflect these cyclic dependencies");
- PG.put_line (COD.report_file,
- "The following dependencies cause cycles : ");
- PG.skip_line (COD.report_file);
- while IDAG.more (e_iter) loop
- IDAG.next (e_iter, from, to);
- temp_string := "A dependency from " & from & " to " & to;
- PG.put_line (COD.report_file, temp_string);
- end loop;
- PG.skip_line (COD.report_file);
- PG.skip_line (COD.report_file);
- end if;
- SP.release;
-
- end report_cycles;
-
- --- Bodies of subprograms local to report_pkg ---
-
-
- procedure add_file_to_dag ( --| procedure which puts the file dependence
- --| info in the file_dag.
- node_label : in SP.string_type --| node to add the info for
- ) is
-
- iter : WDAG.succs_iter;
- node_value : nodes.dag_node;
- dummy_label : SP.string_type;
- file_name : SP.string_type;
- dep_value : nodes.dag_node;
- dep_file : SP.string_type;
-
- begin
-
- node_value := WDAG.get_value (COD.withs_dag, node_label);
- file_name := SP.make_persistent (node_value.file);
- if not SP.equal (file_name, "") then
- begin
- IDAG.add_node (COD.files_dag,
- file_name,
- COD.default_empty_node);
-
- exception
- when IDAG.illegal_node =>
- null;
- end;
- iter := WDAG.make_succs_iter (COD.withs_dag, node_label);
- while WDAG.more (iter) loop
- WDAG.next (iter, dummy_label, dep_value);
- dep_file := dep_value.file;
- if not SP.equal (dep_file, "") then
- begin
- IDAG.add_node (COD.files_dag,
- dep_file,
- COD.default_empty_node);
- IDAG.add_edge (COD.files_dag,
- file_name,
- dep_file);
- exception
- when IDAG.illegal_node =>
- -- just means the node is already there so ignore
- -- it. Still need to add the edge.
- begin
- IDAG.add_edge (COD.files_dag,
- file_name,
- dep_file);
- exception
- when IDAG.makes_cycle =>
- -- need to keep track of where the
- -- cycles are. Unless the cycle is an
- -- an edge from a node to itself. This
- -- happens when one unit in a file withs
- -- another.
- begin
- if not SP.equal (file_name, dep_file)
- then
- IDAG.add_node (COD.cycle_dag,
- file_name,
- COD.default_empty_node);
- IDAG.add_node (COD.cycle_dag,
- dep_file,
- COD.default_empty_node);
- IDAG.add_edge (COD.cycle_dag,
- file_name,
- dep_file);
- end if;
- exception
- when IDAG.illegal_node |
- IDAG.makes_cycle =>
- null;
- end;
- when IDAG.duplicate_edge =>
- -- Two things in one file have a
- -- with in common. this is still ok
- -- so ignore it.
- null;
- end;
- when IDAG.makes_cycle =>
- -- something in the file depends on something else
- -- in the file. This is ok so we can ignore it.
- null;
- when IDAG.duplicate_edge =>
- -- Two things in one file have a with in common
- -- this is still ok so ignore it.
- null;
-
- end;
- end if;
- end loop;
- end if;
-
- end add_file_to_dag;
-
- procedure withs_gen ( --| generates the with dependencies for
- --| the given node
- n : in SP.string_type; --| the node's label
- seen : in out COD.id_set; --| set of nodes already seen
- indent : in out indent_range; --| number of spaces to indent the output
- leaf_list : in out COD.id_list_pkg.list
- --| list of the nodes which are leaves
- ) is
-
- lead_space : integer range 0..line_len;
- output : string (1..line_len);
- successors : WDAG.succs_iter;
- succ : SP.string_type;
- node_value : nodes.dag_node;
- diff : integer range 0..line_len;
- temp_string : SP.string_type;
- new_indent : indent_range;
-
- use string_pkg;
-
- begin
- lead_space := (indent * 2) + 1;
- output := (output'range => ' ');
- node_value := WDAG.get_value (COD.withs_dag, n);
- if COD.id_set_pkg.is_member (seen, n) then
- begin
- output (lead_space..lead_space + SP.length(node_value.name) + 1)
- := "{" & SP.value (node_value.name) & "}";
- PG.put_line (COD.report_file, output);
- exception
- when constraint_error =>
- -- string goes over line_len chars
- SP.mark;
- diff := line_len - lead_space - 1;
- temp_string :=
- "{" & SP.substr (node_value.name, 1, diff) & "}";
- output (lead_space..line_len) :=
- SP.value (temp_string);
- PG.put_line (COD.report_file, output);
- SP.release;
- end;
- else
- COD.id_set_pkg.insert (seen, n);
- node_value := WDAG.get_value (COD.withs_dag, n);
- new_indent := indent + 1;
- begin
- output (lead_space..lead_space + SP.length(node_value.name) - 1)
- := SP.value (node_value.name);
- prev_indent := indent;
- prev_unit := node_value.name;
- PG.put_line (COD.report_file, output);
- exception
- when constraint_error =>
- -- string goes over line_len chars
- output (1..4) := "****";
- output (9..SP.length (prev_unit)+8) :=
- SP.value (prev_unit);
- PG.put_line (COD.report_file, output);
- output := (output'range => ' ');
- if prev_indent = indent then
- output (9..SP.length (node_value.name)+8) :=
- SP.value (node_value.name);
- new_indent := 5;
- else
- output (11..SP.length (node_value.name)+10) :=
- SP.value (node_value.name);
- new_indent := 6;
- end if;
-
- PG.put_line (COD.report_file, output);
- end;
- if WDAG.is_leaf (COD.withs_dag, n) then
- COD.id_list_pkg.attach (leaf_list, n);
- new_indent := new_indent - 1;
- else
- successors := WDAG.make_succs_iter (COD.withs_dag, n);
- while WDAG.more (successors) loop
- WDAG.next (successors, succ);
- withs_gen (succ, seen, new_indent, leaf_list);
- end loop;
- end if;
- end if;
-
- end withs_gen;
- ----------------
- Procedure withed_by_gen ( --| generates the withed-by dependencies for
- --| the given node
- n : in SP.string_type; --| the node's label
- seen : in out COD.id_set; --| set of nodes already seen
- indent : in out indent_range --| number of spaces to indent the output
- ) is
-
- lead_space : integer range 0..line_len;
- output : string (1..line_len);
- preds : WDAG.preds_iter;
- parent : SP.string_type;
- node_value : nodes.dag_node;
- diff : integer range 0..line_len;
- temp_string : SP.string_type;
- new_indent : indent_range;
-
- use string_pkg;
-
- begin
- lead_space := (indent * 2) + 1;
- output := (output'range => ' ');
- node_value := WDAG.get_value (COD.withs_dag, n);
- if COD.id_set_pkg.is_member (seen, n) then
- begin
- output (lead_space..lead_space + SP.length(node_value.name) + 1)
- := "{" & SP.value (node_value.name) & "}";
- PG.put_line (COD.report_file, output);
- exception
- when constraint_error =>
- -- string goes over line_len chars
- SP.mark;
- diff := line_len - lead_space - 1;
- temp_string :=
- "{" & SP.substr (node_value.name, 1, diff) & "}";
- output (lead_space..line_len) :=
- SP.value (temp_string);
- PG.put_line (COD.report_file, output);
- SP.release;
- end;
- else
- COD.id_set_pkg.insert (seen, n);
- new_indent := indent + 1;
- begin
- output (lead_space..lead_space + SP.length(node_value.name) - 1)
- := SP.value (node_value.name);
- prev_indent := indent;
- prev_unit := node_value.name;
- PG.put_line (COD.report_file, output);
- exception
- when constraint_error =>
- -- string goes over line_len chars
- output (1..4) := "****";
- output (9..SP.length (prev_unit)+8) :=
- SP.value (prev_unit);
- PG.put_line (COD.report_file, output);
- output := (output'range => ' ');
- if prev_indent = indent then
- output (9..SP.length (node_value.name)+8) :=
- SP.value (node_value.name);
- new_indent := 5;
- else
- output (11..SP.length (node_value.name)+10) :=
- SP.value (node_value.name);
- new_indent := 6;
- end if;
- PG.put_line (COD.report_file, output);
- end;
- preds := WDAG.make_preds_iter (COD.withs_dag, n);
- while WDAG.more (preds) loop
- WDAG.next (preds, parent);
- withed_by_gen (parent, seen, new_indent);
- end loop;
-
- end if;
-
- end withed_by_gen;
-
- ------------
- end report_pkg;
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --LOOKUP.BDY
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- with string_scanner;
-
- package body lookup_lists is
-
- use string_pkg; -- for "&" etc...
-
- ---- Package Renames:
- package SS renames string_scanner;
-
- procedure add_elt ( --| add a record to the lookup
- --| list
- unit : in SP.string_type; --| unit name of the record
- file : in SP.string_type --| file name of the record
- );
- pragma inline (add_elt);
-
- procedure init_list ( --| initialize the list
- --| from the list in the file
- file : TEXT_IO.file_type
- ) is
- scan : SS.scanner;
- temp : string (1..80);
- last : natural;
- unit_name : SP.string_type;
- unit_type : SP.string_type;
- unit_file : SP.string_type;
- skip_blanks : boolean := true;
- found : boolean;
- begin
- loop
- text_io.get_line (file, temp, last);
- scan := SS.make_scanner (SP.create (temp (1..last)));
- SS.scan_word (scan, found, unit_file, skip_blanks);
- if found then
- if SP.equal (unit_file, "#") then
- SS.scan_word (scan, found, unit_file, skip_blanks);
- end if;
- SS.scan_word (scan, found, unit_name, skip_blanks);
- SS.scan_word (scan, found, unit_type, skip_blanks);
- unit_name := unit_name & " " & unit_type;
- if found then
- add_elt (SP.upper (unit_name), unit_file);
- else
- raise wrong_format;
- end if;
- -- else it might be a blank line in the middle so just
- -- continue reading from the file.
- end if;
- end loop;
- exception
- when text_io.end_error =>
- -- we've finished reading the file
- null;
- end init_list;
-
- function lookup ( --| lookup the file name for
- --| the given unit name.
- unit : in SP.string_type
- )
- return SP.string_type is
-
- iter : l_list_pkg.listIter;
- elt : lookup_record;
- begin
- iter := l_list_pkg.MakeListIter (lookup_list);
- while l_list_pkg.more (iter) loop
- l_list_pkg.next (iter, elt);
- if SP.equal (unit, elt.unit_name) then
- return elt.file_name;
- end if;
- end loop;
- raise not_found;
- end lookup;
-
- procedure add_elt ( --| add a record to the lookup
- --| list
- unit : in SP.string_type; --| unit name of the record
- file : in SP.string_type --| file name of the record
- ) is
- elt : lookup_record;
- begin
- elt := (unit_name => SP.upper (unit),
- file_name => file);
- l_list_pkg.attach (lookup_list, elt);
- end add_elt;
-
- end lookup_lists;
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --CMPUTIL.SPC
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- with string_pkg;
-
- package compile_order_utilities is
- --| The procedures forming the actions on the grammar for compile_order.
-
- --| Overview
-
- --| The procedures are for the most part quite small and explicit in what
- --| they do. The basic functions are to save the program unit name on a stack
- --| when it is seen. Pop and decide what type of unit it is (spec,
- --| body, separate body) when the end is reached. Handle the special case of
- --| adding an addtional with for generic instantiations. If there is a
- --| pragma inline add the compilation unit to the inline set.
- --| Other subprograms add the withs found to a list, process all the dag info
- --| when the end of a compilation unit is reached, process a subunit body
- --| and save the expanded name of a generic instantiation or body (for
- --| subunits).
-
- --| N/A: Effects, Raises, Requires, Modifies
-
- --| Notes
-
- ---- Package Renames:
-
- package SP renames string_pkg;
-
- ---- Operations global to compile_order utilities:
-
- procedure save_unit_name; --| Save the contents of the identifier token
- --| just seen.
-
-
- procedure process_subp_begin;
- --| Save the unit_name last seen on the
- --| stack and if not already set, set the mode
- --| to subp.
-
- procedure process_pkg_begin;
- --| Save the unit_name last seen on the
- --| stack and if not already set, set the mode
- --| to pkg.
-
- procedure process_unit_decl;--| The type of the unit is spec and its name
- --| is the result of popping the stack.
-
- procedure process_unit_body;--| the type of the unit is a body and for the
- --| name pop the stack.
-
- procedure process_subunit; --| the type of the unit is separate body and
- --| there is an additional with of the parent
- --| body. The name of the unit is taken care
- --| of by the processing of the proper body.
-
- procedure get_pragma_id; --| sets a flag if the identifier associated
- --| with a pragma is "INLINE"
-
- procedure process_internal_pragma;
- --| if the inline flag is set, and this is
- --| internal to a subprogram then turn off the
- --| flag
- procedure process_external_pragma;
- --| if the inline flag is set add the last
- --| compilation unit to the inline set.
-
- procedure process_pkg_gen_inst;
- --| add the additional with for the generic
- --| instantiation. in case it is also a
- --| compilation unit the type is spec and the
- --| name is on the top of the stack in this
- --| case.
-
- procedure process_func_gen_inst;
- --| add the additional with for the generic
- --| instantiation. Also, in case this is
- --| a compilation unit the type is spec and the
- --| name is the last unit name saved.
-
- procedure process_subp_gen_inst;
- --| add the additional with for the generic
- --| instantiation. in case it is also a
- --| compilation unit the type is spec and the
- --| name is on the top of the stack in this
- --| case.
-
- procedure add_with_to_list; --| add the value of the last identifier
- --| to the withs_list.
-
- procedure process_dag_info; --| put all the information gathered into
- --| a dag. Done when we have reached the
- --| end of a compilation unit.
-
- procedure begin_generic_name;
- --| begin to save the name of the generic
- --| being instantiated.
-
- procedure begin_body_name; --| begin to save the name of the parent
- --| body in the case of a separate body.
-
- procedure continue_body_name;
- --| append to the body name. Needed since the
- --| body name could be an expanded name like
- --| a.b.c
-
-
- procedure push_stack ( --| push the given name on the name
- --| stack.
- element : SP.string_type
- );
-
- function pop_stack --| returns the name on the top of the stack
- return SP.string_type;
-
- end compile_order_utilities;
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --CMPUTIL.BDY
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- with compile_order_declarations;
- use compile_order_declarations;
- with ParserDeclarations;
- with units_dag_pkg;
- with mini_dag_pkg;
- with nodes;
-
- package body compile_order_utilities is
- --| The procedures forming the actions on the grammar for compile_order.
-
- --| Overview
-
- --| The procedures are for the most part quite small and explicit in what
- --| they do. The basic functions are to save the program unit name on a stack
- --| when it is seen. Pop and decide what type of unit it is (spec,
- --| body, separate body) when the end is reached. Handle the special case of
- --| adding an addtional with for generic instantiations. If there is a
- --| pragma inline add the compilation unit to the inline set.
- --| Other subprograms add the withs found to a list, process all the dag info
- --| when the end of a compilation unit is reached, process a subunit body
- --| and save the expanded name of a generic instantiation or body (for
- --| subunits).
-
- --| N/A: Effects, Raises, Requires, Modifies
-
- --| Notes
-
- --| All the variables used in the global subprograms are in compile_order_
- --| declarations, so they are not qualified.
-
- use string_pkg; -- for "&" etc...
-
- --- Package Renames
-
- package COD renames compile_order_declarations;
- package WDAG renames units_dag_pkg; -- WDAG for withs dag
- package IDAG renames mini_dag_pkg; -- IDAG for info dag
-
-
- --- Local operation specifications ---
-
- function string_of ( --| function that returns the string rep
- --| of the source text of a token
- token_text: in PD.Source_Text --| input source text
- )
- return SP.string_type;
-
- procedure put_info_in_dag ( --| procedure which puts all the withs info
- --| into the dag.
- node_label : in SP.string_type; --| parent node in the dag
- info_list : --| withs list accumulated
- in out COD.id_list_pkg.list
- );
-
- --| Effects: For the node given add an edge from it to each node
- --| in the info_list. If either of the nodes do not already exist
- --| create them and put in any values which are known. i.e. the filename
- --| for the node_label is the current file. It also empties the with_list
- --| as it goes.
-
- --| Modifies: info_list
-
-
-
- --- Operations global to compile_order_utilities ---
-
- procedure save_unit_name --| Save the contents of the identifier token
- --| just seen.
- is
- begin
- unit_name := string_of (prev_token.lexed_token.text);
- end save_unit_name;
-
- procedure process_subp_begin
- --| Save the unit_name last seen on the
- --| stack and if not already set, set the mode
- --| to subp.
- is
- begin
- if mode = nothing then mode := subp; end if;
- push_stack (unit_name);
- end process_subp_begin;
-
- procedure process_pkg_begin
- --| Save the unit_name last seen on the
- --| stack and if not already set, set the mode
- --| to pkg.
- is
- begin
- if mode = nothing then mode := pkg; end if;
- push_stack (unit_name);
- end process_pkg_begin;
-
- procedure process_unit_decl --| The type of the unit is spec and its name
- --| is the result of popping the stack.
- is
- begin
- unit_type := spec;
- if cu_name /= SP.create ("") then
- SP.flush (cu_name);
- end if;
- cu_name := SP.make_persistent (pop_stack);
- end process_unit_decl;
-
- procedure process_unit_body --| the type of the unit is a body and for the
- --| name pop the stack.
- is
- begin
- unit_type := bdy;
- if cu_name /= SP.create ("") then
- SP.flush (cu_name);
- end if;
- cu_name := SP.make_persistent (pop_stack);
-
- end process_unit_body;
-
- procedure process_subunit --| the type of the unit is separate body and
- --| there is an additional with of the parent
- --| body. The name of the unit is taken care
- --| of by the processing of the proper body.
- is
- begin
- unit_type := separate_body;
- id_list_pkg.attach (withs_list,
- SP.make_persistent (parent_body_name &
- " (body)"));
- end process_subunit;
-
- procedure get_pragma_id --| sets a flag if the identifier associated
- --| with a pragma is "INLINE"
- is
- begin
- if SP.equal (SP.upper (string_of (prev_token.lexed_token.text)),
- "INLINE") then
- inline_flag := true;
- end if;
- end get_pragma_id;
-
- procedure process_internal_pragma
- --| if the inline flag is set, and this is
- --| internal to a subprogram then turn off the
- --| flag
- is
- begin
- if inline_flag and mode = subp then
- inline_flag := false;
- end if;
- end process_internal_pragma;
-
- procedure process_external_pragma
- --| if the inline flag is set add the last
- --| compilation unit to the inline set.
- is
- begin
- if inline_flag then
- if not id_set_pkg.is_member (inline_set, cu_name)
- then
- id_set_pkg.insert (inline_set,
- SP.make_persistent (cu_name));
- end if;
- inline_flag := false;
- end if;
- end process_external_pragma;
-
-
- procedure process_pkg_gen_inst
- --| add the additional with for the generic
- --| instantiation. in case it is also a
- --| compilation unit the type is spec and the
- --| name is on the top of the stack in this
- --| case.
- is
- temp_list : id_list_pkg.list := id_list_pkg.create;
- pkg_name : SP.string_type;
- temp_current_file : SP.string_type;
- begin
- -- create the dependency if the flag in compile_order_declarations
- -- is set.
- if do_generics then
- -- make the package name from the generic name and add it to
- -- the withs list to create the right dependency.
- pkg_name := SP.make_persistent (generic_name & " (body)");
- id_list_pkg.attach (withs_list, pkg_name);
-
- -- since you can't have an instantiation without a with of the
- -- spec make sure that the spec and body of pkg have the right
- -- dependencies by doing a little put_info_in_dag w/ temp_list
- id_list_pkg.attach (temp_list,
- SP.make_persistent (generic_name
- & " (spec)"));
- -- have to change current file so the instantiation doesn't
- -- have current name.
- temp_current_file := SP.make_persistent (current_file);
- current_file := SP.create ("");
- put_info_in_dag (pkg_name, temp_list);
- current_file := temp_current_file;
- id_list_pkg.destroy (temp_list);
-
- end if;
-
- if cu_name /= SP.create ("") then
- SP.flush (cu_name);
- end if;
- cu_name := SP.make_persistent (pop_stack);
- unit_type := spec;
- if mode = nothing then mode := pkg; end if;
- end process_pkg_gen_inst;
-
-
- procedure process_func_gen_inst
- --| add the additional with for the generic
- --| instantiation. Also, in case this is
- --| a compilation unit the type is spec and the
- --| name is the last unit name saved.
- is
- temp_list : id_list_pkg.list := id_list_pkg.create;
- func_name : SP.string_type;
- temp_current_file : SP.string_type;
- begin
-
- -- create the dependency if the flag in compile_order_declarations
- -- is set.
- if do_generics then
- -- make the function name from the generic name and add it to
- -- the withs list to create the right dependency.
- func_name := SP.make_persistent (generic_name & " (body)");
- id_list_pkg.attach (withs_list, func_name);
-
- -- since you can't have an instantiation without a with of the
- -- spec make sure that the spec and body of func have the right
- -- dependencies by doing a little put_info_in_dag w/ temp_list.
- id_list_pkg.attach (temp_list,
- SP.make_persistent (generic_name
- & " (spec)"));
- -- have to change current file so the instantiation doesn't
- -- have current name.
- temp_current_file := SP.make_persistent (current_file);
- current_file := SP.create ("");
- put_info_in_dag (func_name, temp_list);
- current_file := temp_current_file;
- id_list_pkg.destroy (temp_list);
-
- end if;
-
- if cu_name /= SP.create ("") then
- SP.flush (cu_name);
- end if;
- cu_name := SP.make_persistent (unit_name);
- unit_type := spec;
- if mode = nothing then mode := subp; end if;
- end process_func_gen_inst;
-
- procedure process_subp_gen_inst
- --| add the additional with for the generic
- --| instantiation. in case it is also a
- --| compilation unit the type is spec and the
- --| name is on the top of the stack in this
- --| case.
- is
- temp_list : id_list_pkg.list := id_list_pkg.create;
- subp_name : SP.string_type;
- temp_current_file : SP.string_type;
-
- begin
- -- create the dependency if the flag in compile_order_declarations
- -- is set.
- if do_generics then
- -- make the subprogram name from the generic name and add it to
- -- the withs list to create the right dependency.
- subp_name := SP.make_persistent (generic_name & " (body)");
- id_list_pkg.attach (withs_list, subp_name);
-
- -- since you can't have an instantiation without a with of the
- -- spec make sure that the spec and body of subp have the right
- -- dependencies by doing a little put_info_in_dag w/ temp_list.
- id_list_pkg.attach (temp_list,
- SP.make_persistent (generic_name
- & " (spec)"));
- -- have to change current file so the instantiation doesn't
- -- have current name.
- temp_current_file := SP.make_persistent (current_file);
- current_file := SP.create ("");
- put_info_in_dag (subp_name, temp_list);
- current_file := temp_current_file;
- id_list_pkg.destroy (temp_list);
-
- end if;
-
- if cu_name /= SP.create ("") then
- SP.flush (cu_name);
- end if;
- cu_name := SP.make_persistent (pop_stack);
- unit_type := spec;
- if mode = nothing then mode := subp; end if;
- end process_subp_gen_inst;
-
-
- procedure add_with_to_list --| add the value of the last identifier
- --| to the withs_list.
- is
- begin
- id_list_pkg.attach (withs_list,
- SP.make_persistent
- (string_of (prev_token.lexed_token.text)
- & " (spec)"));
- end add_with_to_list;
-
- procedure process_dag_info --| put all the information gathered into
- --| a dag. Done when we have reached the
- --| end of a compilation unit.
- is
- name : SP.string_type;
-
- begin
- if unit_type = bdy then
- id_list_pkg.attach (withs_list,
- SP.make_persistent (cu_name & " (spec)"));
- name := SP.make_persistent (cu_name & " (body)");
- elsif unit_type = separate_body then
- name := SP.make_persistent (cu_name & " (separate body)");
- else
- name := SP.make_persistent (cu_name & " (spec)");
- end if;
- if inline_flag then
- if not id_set_pkg.is_member (inline_set, cu_name) then
- id_set_pkg.insert (inline_set,
- SP.make_persistent (cu_name));
- end if;
- inline_flag := false;
- end if;
- id_list_pkg.attach (unit_list, name);
- begin
- put_info_in_dag (name, withs_list);
- exception
- when COD.duplicate_name =>
- -- the withs list has to be emptied before
- -- we resignal the duplicate name, otherwise
- -- the unit in the next file inherits the withs
- -- of the duplicate one. Same goes for resetting
- -- the flags.
- COD.id_list_pkg.destroy (COD.withs_list);
- mode := nothing;
- inline_flag := false;
- raise COD.duplicate_name;
- end;
- mode := nothing;
- inline_flag := false;
- end process_dag_info;
-
- procedure begin_generic_name
- --| begin to save the name of the generic
- --| being instantiated.
- is
- begin
- generic_name := string_of (prev_token.lexed_token.text);
- end begin_generic_name;
-
-
- procedure begin_body_name --| begin to save the name of the parent
- --| body in the case of a separate body.
- is
- begin
- parent_body_name := string_of (prev_token.lexed_token.text);
- end begin_body_name;
-
- procedure continue_body_name
- --| append to the body name. Needed since the
- --| body name could be an expanded name like
- --| a.b.c
- is
- begin
- parent_body_name := SP."&" (parent_body_name,
- string_of (prev_token.lexed_token.text));
- end continue_body_name;
-
-
- --- Bodies of local subprograms ---
-
- function string_of ( --| function that returns the string rep
- --| of the source text of a token
- token_text: in PD.Source_Text --| input source text
- )
- return SP.string_type is
-
- begin
- return SP.create (PD.Get_Source_Text (token_text));
- end string_of;
-
-
- procedure push_stack ( --| push the given name on the name
- --| stack.
- element : SP.string_type
- ) is
- begin
- id_list_pkg.attach (element, COD.name_stack);
- end push_stack;
-
- function pop_stack --| returns the name on the top of the stack
- return SP.string_type is
- temp : SP.string_type;
- begin
- temp := id_list_pkg.FirstValue (COD.name_stack);
- id_list_pkg.DeleteHead (COD.name_stack);
- return temp;
- end pop_stack;
-
- procedure put_info_in_dag ( --| procedure which puts all the withs info
- --| into the dag.
- node_label : in SP.string_type; --| parent node in the dag
- info_list : --| withs list accumulated
- in out COD.id_list_pkg.list
- ) is
-
-
- -- default_node must be declared in somewhere like comp_decls
- -- along with the instantiation of the dag and similar things.
- -- if node_label ~element (with_info) then
- -- add_node (with_info, node_label, default_node)
- -- end if
-
- -- for each with in info_list do
- -- if with ~element(with_info) then
- -- add_node (with_info, with, default_node)
- -- end if
- -- add_edge (with_info, node_label, with)
- -- end for
-
- i : COD.id_list_pkg.listiter;
- with_node : SP.string_type;
- with_name : SP.string_type;
- label : SP.string_type;
- value : nodes.dag_node;
- gen_inst : boolean;
- begin
- SP.mark;
-
- begin
- -- get the value of the node and change the filename to be the
- -- current file. If the filename is not the empty string this
- -- implies we have seen something with this name before so raise
- -- duplicate name since this is not allowed at the library unit
- -- level. If illegal_node is raised the node does not exist so
- -- create it.
- label := SP.upper (node_label);
-
- value := WDAG.get_value (COD.withs_dag, label);
- gen_inst := SP.equal (COD.current_file, "");
- -- current file will only be null before any files are read or
- -- when we are doing a generic instantiation which shouldn't
- -- effect the file name.
- if not SP.equal (value.file, "") and
- not gen_inst then
- COD.dup_string := SP.make_persistent (value.name);
- COD.dup_file := SP.make_persistent (value.file);
- SP.release;
- raise COD.duplicate_name;
- end if;
- if not gen_inst then
- value.file := SP.make_persistent (COD.current_file);
- value.name := SP.make_persistent (node_label);
- WDAG.set_value (COD.withs_dag, label, value);
- end if;
- exception
- when WDAG.illegal_node =>
- -- the node doesn't exist yet so we must add it
- value := COD.default_node;
- value.file := SP.make_persistent (COD.current_file);
- value.name := SP.make_persistent (node_label);
- WDAG.add_node (withs_dag,
- SP.make_persistent (label),
- value);
- end;
-
- i := COD.id_list_pkg.MakeListIter (info_list);
- while COD.id_list_pkg.more (i) loop
- COD.id_list_pkg.next (i, with_name);
- begin
- with_node := SP.make_persistent (SP.upper (with_name));
- value := COD.default_node;
- value.name := SP.make_persistent (with_name);
- WDAG.add_node (COD.withs_dag,
- with_node,
- value);
- WDAG.add_edge (COD.withs_dag, label, with_node);
-
- exception
- when WDAG.illegal_node =>
- -- raised when the with_node is already in the dag. No
- -- harm done so ignore the error and add the edge.
- begin
- WDAG.add_edge (COD.withs_dag, label, with_node);
- exception
- when WDAG.makes_cycle =>
- begin
- IDAG.add_node (COD.cycle_dag,
- SP.make_persistent(label),
- COD.default_empty_node);
- IDAG.add_node (COD.cycle_dag,
- SP.make_persistent (with_node),
- COD.default_empty_node);
- IDAG.add_edge (COD.cycle_dag,
- label,
- with_node);
- exception
- when IDAG.illegal_node |
- IDAG.makes_cycle =>
- null;
- end;
- when WDAG.duplicate_edge =>
- null;
- end;
- when WDAG.makes_cycle =>
- -- need to keep track of where the cycles are.
- begin
- IDAG.add_node (COD.cycle_dag,
- SP.make_persistent (label),
- COD.default_empty_node);
- IDAG.add_node (COD.cycle_dag,
- SP.make_persistent (with_node),
- COD.default_empty_node);
- IDAG.add_edge (COD.cycle_dag, label, with_node);
-
- exception
- when IDAG.illegal_node | IDAG.makes_cycle =>
- null;
- end;
- end;
-
- end loop;
-
- -- should here free all the strings in the list
- COD.id_list_pkg.destroy (info_list);
- SP.release;
-
- end put_info_in_dag;
-
-
- end compile_order_utilities;
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --APPLYACT.SUB
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
-
- with compile_order_declarations;
- with compile_order_utilities;
-
- separate (Parser)
- procedure Apply_Actions(Rule_Number : in PT.LeftHandSideRange) is
- -- all procedure calls in this unit are procedures in package
- -- compile_order_utilities
-
- use compile_order_utilities;
-
- -- all variables are from compile_order declarations
-
- use compile_order_declarations;
-
- begin
-
- case Rule_Number is
-
- ----------------------------------------------------------------------
- -- pragma ::= PRAGMA pragma_id ( general_component_associations ) ;
-
-
- when 1 =>
-
-
- process_internal_pragma;
- ----------------------------------------------------------------------
- -- pragma_id ::= identifier
-
-
- when 3 =>
-
-
- get_pragma_id;
- ----------------------------------------------------------------------
- -- subprogram_declaration ::= subprogram_specification ;
-
-
- when 214 =>
-
-
- process_unit_decl;
- ----------------------------------------------------------------------
- -- subprogram_specification ::= PROCEDURE unit_identifier
-
-
- when 215 |
-
-
-
- --....................................................................
- -- subprogram_specification ::= PROCEDURE unit_identifier (
- -- parameter_specification {;parameter_specification} )
-
-
- 216 |
-
-
-
- --....................................................................
- -- subprogram_specification ::= FUNCTION designator RETURN type_mark
-
-
- 217 |
-
-
-
- --....................................................................
- -- subprogram_specification ::= FUNCTION designator ( parameter_specification
- -- {;parameter_specification} ) RETURN type_mark
-
-
- 218 =>
-
-
- process_subp_begin;
- ----------------------------------------------------------------------
- -- unit_identifier ::= identifier
-
-
- when 219 |
-
-
-
- --....................................................................
- -- designator ::= identifier
-
-
- 220 |
-
-
-
- --....................................................................
- -- designator ::= string_literal
-
-
- 221 =>
-
-
- save_unit_name;
- ----------------------------------------------------------------------
- -- subprogram_body ::= subprogram_specification IS
- -- declarative_part__begin_end_block [end_designator] ;
-
-
- when 228 =>
-
-
- process_unit_body;
- ----------------------------------------------------------------------
- -- package_declaration ::= package_specification ;
-
-
- when 230 =>
-
-
- process_unit_decl;
- ----------------------------------------------------------------------
- -- package_body ::= package__body__unit_identifier IS declarative_part END
- -- [identifier] ;
-
-
- when 233 |
-
-
-
- --....................................................................
- -- package_body ::= package__body__unit_identifier IS
- -- declarative_part__begin_end_block [identifier] ;
-
-
- 234 =>
-
-
- process_unit_body;
- ----------------------------------------------------------------------
- -- package__unit_identifier ::= PACKAGE unit_identifier
-
-
- when 235 =>
-
-
- process_pkg_begin;
- ----------------------------------------------------------------------
- -- package__body__unit_identifier ::= PACKAGE BODY unit_identifier
-
-
- when 236 =>
-
-
- process_pkg_begin;
- ----------------------------------------------------------------------
- -- renaming_declaration ::= subprogram_specification RENAMES name ;
-
-
- when 245 =>
-
-
- dummy := pop_stack;
- ----------------------------------------------------------------------
- -- compilation_unit ::= pragma_header ( general_component_associations ) ;
-
-
- when 273 =>
-
-
- process_external_pragma;
- ----------------------------------------------------------------------
- -- compilation_unit ::= context_clause library_or_secondary_unit
-
-
- when 275 =>
-
-
- process_dag_info;
- ----------------------------------------------------------------------
- -- with_id ::= identifier
-
-
- when 285 =>
-
-
- add_with_to_list;
- ----------------------------------------------------------------------
- -- body_stub ::= subprogram_specification IS SEPARATE ;
-
-
- when 288 =>
-
-
- dummy := pop_stack;
- ----------------------------------------------------------------------
- -- body_stub ::= package__body__unit_identifier IS SEPARATE ;
-
-
- when 289 =>
-
-
- dummy := pop_stack;
- ----------------------------------------------------------------------
- -- subunit ::= SEPARATE ( body_name ) proper_body
-
-
- when 291 =>
-
-
- process_subunit;
- ----------------------------------------------------------------------
- -- generic_declaration ::= generic_specification ;
-
-
- when 298 =>
-
-
- process_unit_decl;
- ----------------------------------------------------------------------
- -- generic_parameter_declaration ::= WITH subprogram_specification
- -- [IS__name__or__<>] ;
-
-
- when 305 =>
-
-
- dummy := pop_stack;
- ----------------------------------------------------------------------
- -- generic_instantiation ::= package__unit_identifier IS NEW generic_name ;
-
-
- when 314 |
-
-
-
- --....................................................................
- -- generic_instantiation ::= package__unit_identifier IS NEW generic_name (
- -- generic_association {,generic_association} ) ;
-
-
- 315 =>
-
-
- process_pkg_gen_inst;
- ----------------------------------------------------------------------
- -- generic_instantiation ::= FUNCTION designator IS NEW generic_name ;
-
-
- when 316 |
-
-
-
- --....................................................................
- -- generic_instantiation ::= FUNCTION designator IS NEW generic_name (
- -- generic_association {,generic_association} ) ;
-
-
- 317 =>
-
-
- process_func_gen_inst;
- ----------------------------------------------------------------------
- -- generic_instantiation ::= subprogram_specification IS NEW generic_name ;
-
-
- when 318 |
-
-
-
- --....................................................................
- -- generic_instantiation ::= subprogram_specification IS NEW generic_name (
- -- generic_association {,generic_association} ) ;
-
-
- 319 =>
-
-
- process_subp_gen_inst;
- ----------------------------------------------------------------------
- -- body_name ::= identifier
-
-
- when 351 =>
-
-
- begin_body_name;
- ----------------------------------------------------------------------
- -- body_name ::= body_name . identifier
-
-
- when 352 =>
-
-
- continue_body_name;
- ----------------------------------------------------------------------
- -- generic_name ::= identifier
-
-
- when 353 =>
-
-
- begin_generic_name;
-
- when others =>
- null;
- end case;
- end Apply_Actions;
-
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- --GETNEXT.SUB
- --::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
- with compile_order_declarations; use compile_order_declarations;
-
- separate (Lex)
- function GetNextNonCommentToken return PD.ParseStackElement is
- begin
-
- prev_token := CST;
-
- loop
- CST := GetNextSourceToken;
- -- CST is the current source Token which is a
- -- PD.ParseStackElement
- exit when (CST.gram_sym_val = PT.EOF_TokenValue) or
- (CST.gram_sym_val /= PT.Comment_TokenValue);
-
- -- comments are ignored in compile_order.
-
- end loop;
- return CST; -- return the token that is not a comment
- end GetNextNonCommentToken;
-
-
-