DataMuseum.dk

Presents historical artifacts from the history of:

Rational R1000/400

This is an automatic "excavation" of a thematic subset of
artifacts from Datamuseum.dk's BitArchive.

See our Wiki for more about Rational R1000/400

Excavated with: AutoArchaeologist - Free & Open Source Software.


top - download

⟦2c4c78d6e⟧ Ada Source

    Length: 38912 (0x9800)
    Types: Ada Source
    Notes: 03_class, FILE, R1k_Segment, e3_tag, package body Parser, seg_030b23

Derivation

└─⟦8527c1e9b⟧ Bits:30000544 8mm tape, Rational 1000, Arrival backup of disks in PAM's R1000
    └─ ⟦cfc2e13cd⟧ »Space Info Vol 2« 
        └─⟦this⟧ 

E3 Source Code



package body Parser is
-- build_eof_action - build the "<<EOF>>" action for the active start
--                    conditions

    use Text_Io, Misc_Defs;
    procedure Build_Eof_Action is
    begin
        Text_Io.Put (Temp_Action_File, "when ");
        for I in 1 .. Actvp loop
            if (Sceof (Actvsc (I))) then
                Text_Io.Put (Standard_Error,
                             "multiple <<EOF>> rules for start condition ");
                Tstring.Put (Standard_Error, Scname (Actvsc (I)));
                Main_Body.Aflexend (1);
            else
                Sceof (Actvsc (I)) := True;
                Text_Io.Put (Temp_Action_File, "YY_END_OF_BUFFER +");
                Tstring.Put (Temp_Action_File, Scname (Actvsc (I)));
                Text_Io.Put_Line (Temp_Action_File, " + 1 ");
                if (I /= Actvp) then
                    Text_Io.Put_Line (Temp_Action_File, " |");
                else
                    Text_Io.Put_Line (Temp_Action_File, " =>");
                end if;
            end if;
        end loop;
        Misc.Line_Directive_Out (Temp_Action_File);
    end Build_Eof_Action;

--  yyerror - eat up an error message from the parser
--
--  synopsis
--     char msg[];
--     yyerror( msg );

    procedure Yyerror (Msg : String) is
    begin
        null;
    end Yyerror;

    use Parse_Goto, Parse_Shift_Reduce, Text_Io, Misc_Defs, Tstring;
    procedure Yyparse is

        -- Rename User Defined Packages to Internal Names.
        package Yy_Goto_Tables renames Parse_Goto;
        package Yy_Shift_Reduce_Tables renames Parse_Shift_Reduce;
        package Yy_Tokens renames Parse_Tokens;

        use Yy_Tokens, Yy_Goto_Tables, Yy_Shift_Reduce_Tables;

        procedure Yyerrok;
        procedure Yyclearin;

        package Yy is

            -- the size of the value and state stacks
            Stack_Size : constant Natural := 300;

            -- subtype rule         is natural;
            subtype Parse_State is Natural;
            -- subtype nonterminal  is integer;

            -- encryption constants
            Default : constant := -1;
            First_Shift_Entry : constant := 0;
            Accept_Code : constant := -1001;
            Error_Code : constant := -1000;

            -- stack data used by the parser
            Tos : Natural := 0;
            Value_Stack : array (0 .. Stack_Size) of Yy_Tokens.Yystype;
            State_Stack : array (0 .. Stack_Size) of Parse_State;

            -- current input symbol and action the parser is on
            Action : Integer;
            Rule_Id : Rule;
            Input_Symbol : Yy_Tokens.Token;


            -- error recovery flag
            Error_Flag : Natural := 0;
            -- indicates  3 - (number of valid shifts after an error occurs)

            Look_Ahead : Boolean := True;
            Index : Integer;

            -- Is Debugging option on or off
            Debug : constant Boolean := False;

        end Yy;


        function Goto_State (State : Yy.Parse_State; Sym : Nonterminal)
                            return Yy.Parse_State;

        function Parse_Action (State : Yy.Parse_State; T : Yy_Tokens.Token)
                              return Integer;

        pragma Inline (Goto_State, Parse_Action);


        function Goto_State (State : Yy.Parse_State; Sym : Nonterminal)
                            return Yy.Parse_State is
            Index : Integer;
        begin
            Index := Goto_Offset (State);
            while Integer (Goto_Matrix (Index).Nonterm) /= Sym loop
                Index := Index + 1;
            end loop;
            return Integer (Goto_Matrix (Index).Newstate);
        end Goto_State;


        function Parse_Action (State : Yy.Parse_State; T : Yy_Tokens.Token)
                              return Integer is
            Index : Integer;
            Tok_Pos : Integer;
            Default : constant Integer := -1;
        begin
            Tok_Pos := Yy_Tokens.Token'Pos (T);
            Index := Shift_Reduce_Offset (State);
            while Integer (Shift_Reduce_Matrix (Index).T) /= Tok_Pos and then
                     Integer (Shift_Reduce_Matrix (Index).T) /= Default loop
                Index := Index + 1;
            end loop;
            return Integer (Shift_Reduce_Matrix (Index).Act);
        end Parse_Action;

-- error recovery stuff

        procedure Handle_Error is
            Temp_Action : Integer;
        begin

            if Yy.Error_Flag = 3 then -- no shift yet, clobber input.
                if Yy.Debug then
                    Put_Line ("Ayacc.YYParse: Error Recovery Clobbers " &
                              Yy_Tokens.Token'Image (Yy.Input_Symbol));
                end if;
                if Yy.Input_Symbol = Yy_Tokens.
                                        End_Of_Input then  -- don't discard,
                    if Yy.Debug then
                        Put_Line
                           ("Ayacc.YYParse: Can't discard END_OF_INPUT, quiting...");
                    end if;
                    raise Yy_Tokens.Syntax_Error;
                end if;

                Yy.Look_Ahead := True;   -- get next token
                return;                  -- and try again...
            end if;

            if Yy.Error_Flag = 0 then -- brand new error
                Yyerror ("Syntax Error");
            end if;

            Yy.Error_Flag := 3;

            -- find state on stack where error is a valid shift --

            if Yy.Debug then
                Put_Line
                   ("Ayacc.YYParse: Looking for state with error as valid shift");
            end if;

            loop
                if Yy.Debug then
                    Put_Line ("Ayacc.YYParse: Examining State " &
                              Yy.Parse_State'Image (Yy.State_Stack (Yy.Tos)));
                end if;
                Temp_Action := Parse_Action (Yy.State_Stack (Yy.Tos), Error);

                if Temp_Action >= Yy.First_Shift_Entry then
                    Yy.Tos := Yy.Tos + 1;
                    Yy.State_Stack (Yy.Tos) := Temp_Action;
                    exit;
                end if;

                Decrement_Stack_Pointer:
                    begin
                        Yy.Tos := Yy.Tos - 1;
                    exception
                        when Constraint_Error =>
                            Yy.Tos := 0;
                    end Decrement_Stack_Pointer;

                if Yy.Tos = 0 then
                    if Yy.Debug then
                        Put_Line
                           ("Ayacc.YYParse: Error recovery popped entire stack, aborting...");
                    end if;
                    raise Yy_Tokens.Syntax_Error;
                end if;
            end loop;

            if Yy.Debug then
                Put_Line ("Ayacc.YYParse: Shifted error token in state " &
                          Yy.Parse_State'Image (Yy.State_Stack (Yy.Tos)));
            end if;

        end Handle_Error;

        -- print debugging information for a shift operation
        procedure Shift_Debug (State_Id : Yy.Parse_State;
                               Lexeme : Yy_Tokens.Token) is
        begin
            Put_Line ("Ayacc.YYParse: Shift " &
                      Yy.Parse_State'Image (State_Id) & " on input symbol " &
                      Yy_Tokens.Token'Image (Lexeme));
        end Shift_Debug;

        -- print debugging information for a reduce operation
        procedure Reduce_Debug (Rule_Id : Rule; State_Id : Yy.Parse_State) is
        begin
            Put_Line ("Ayacc.YYParse: Reduce by rule " & Rule'Image (Rule_Id) &
                      " goto state " & Yy.Parse_State'Image (State_Id));
        end Reduce_Debug;

        -- make the parser believe that 3 valid shifts have occured.
        -- used for error recovery.
        procedure Yyerrok is
        begin
            Yy.Error_Flag := 0;
        end Yyerrok;

        -- called to clear input symbol that caused an error.
        procedure Yyclearin is
        begin
            -- yy.input_symbol := yylex;
            Yy.Look_Ahead := True;
        end Yyclearin;


    begin
        -- initialize by pushing state 0 and getting the first input symbol
        Yy.State_Stack (Yy.Tos) := 0;

        loop

            Yy.Index := Shift_Reduce_Offset (Yy.State_Stack (Yy.Tos));
            if Integer (Shift_Reduce_Matrix (Yy.Index).T) = Yy.Default then
                Yy.Action := Integer (Shift_Reduce_Matrix (Yy.Index).Act);
            else
                if Yy.Look_Ahead then
                    Yy.Look_Ahead := False;
                    Yy.Input_Symbol := Yylex;
                end if;
                Yy.Action := Parse_Action
                                (Yy.State_Stack (Yy.Tos), Yy.Input_Symbol);
            end if;

            if Yy.Action >= Yy.First_Shift_Entry then  -- SHIFT

                if Yy.Debug then
                    Shift_Debug (Yy.Action, Yy.Input_Symbol);
                end if;

                -- Enter new state
                Yy.Tos := Yy.Tos + 1;
                Yy.State_Stack (Yy.Tos) := Yy.Action;
                Yy.Value_Stack (Yy.Tos) := Yylval;

                if Yy.Error_Flag > 0 then  -- indicate a valid shift
                    Yy.Error_Flag := Yy.Error_Flag - 1;
                end if;

                -- Advance lookahead
                Yy.Look_Ahead := True;

            elsif Yy.Action = Yy.Error_Code then       -- ERROR
                Handle_Error;

            elsif Yy.Action = Yy.Accept_Code then
                if Yy.Debug then
                    Put_Line ("Ayacc.YYParse: Accepting Grammar...");
                end if;
                exit;

            else -- Reduce Action

                 -- Convert action into a rule
                Yy.Rule_Id := -1 * Yy.Action;

                -- Execute User Action
                -- user_action(yy.rule_id);
                case Yy.Rule_Id is

                    when 1 =>
--#line  44
                        -- add default rule

                        Pat := Ccl.Cclinit;
                        Ccl.Cclnegate (Pat);

                        Def_Rule := Nfa.Mkstate (-Pat);

                        Nfa.Finish_Rule (Def_Rule, False, 0, 0);

                        for I in 1 .. Lastsc loop
                            Scset (I) := Nfa.Mkbranch (Scset (I), Def_Rule);
                        end loop;

                        if (Spprdflt) then
                            Text_Io.Put (Temp_Action_File,
                                         "raise AFLEX_SCANNER_JAMMED;");
                        else
                            Text_Io.Put (Temp_Action_File, "ECHO");

                            Text_Io.Put_Line (Temp_Action_File, ";");
                        end if;


                    when 2 =>
--#line  69

                        -- initialize for processing rules

                        -- create default DFA start condition
                        Sym.Scinstal (Tstring.Vstr ("INITIAL"), False);


                    when 5 =>
--#line  80
                        Misc.Synerr ("unknown error processing section 1");

                    when 7 =>
--#line  87

                        -- these productions are separate from the s1object
                        -- rule because the semantics must be done before
                        -- we parse the remainder of an s1object


                        Xcluflg := False;


                    when 8 =>
--#line  97
                        Xcluflg := True;

                    when 9 =>
--#line  101
                        Sym.Scinstal (Nmstr, Xcluflg);

                    when 10 =>
--#line  104
                        Sym.Scinstal (Nmstr, Xcluflg);

                    when 11 =>
--#line  107
                        Misc.Synerr ("bad start condition list");

                    when 14 =>
--#line  115

                        -- initialize for a parse of one rule
                        Trlcontxt := False;
                        Variable_Trail_Rule := False;
                        Varlength := False;
                        Trailcnt := 0;
                        Headcnt := 0;
                        Rulelen := 0;
                        Current_State_Enum := State_Normal;
                        Previous_Continued_Action := Continued_Action;
                        Nfa.New_Rule;


                    when 15 =>
--#line  130

                        Pat := Nfa.Link_Machines (Yy.Value_Stack (Yy.Tos - 1),
                                                  Yy.Value_Stack (Yy.Tos));
                        Nfa.Finish_Rule (Pat, Variable_Trail_Rule,
                                         Headcnt, Trailcnt);

                        for I in 1 .. Actvp loop
                            Scbol (Actvsc (I)) := Nfa.Mkbranch
                                                     (Scbol (Actvsc (I)), Pat);
                        end loop;

                        if (not Bol_Needed) then
                            Bol_Needed := True;

                            if (Performance_Report) then
                                Text_Io.Put
                                   (Standard_Error,
                                    "'^' operator results in sub-optimal performance");
                                Text_Io.New_Line (Standard_Error);
                            end if;
                        end if;


                    when 16 =>
--#line  152

                        Pat := Nfa.Link_Machines (Yy.Value_Stack (Yy.Tos - 1),
                                                  Yy.Value_Stack (Yy.Tos));
                        Nfa.Finish_Rule (Pat, Variable_Trail_Rule,
                                         Headcnt, Trailcnt);

                        for I in 1 .. Actvp loop
                            Scset (Actvsc (I)) := Nfa.Mkbranch
                                                     (Scset (Actvsc (I)), Pat);
                        end loop;


                    when 17 =>
--#line  163

                        Pat := Nfa.Link_Machines (Yy.Value_Stack (Yy.Tos - 1),
                                                  Yy.Value_Stack (Yy.Tos));
                        Nfa.Finish_Rule (Pat, Variable_Trail_Rule,
                                         Headcnt, Trailcnt);

                        -- add to all non-exclusive start conditions,
                        -- including the default (0) start condition

                        for I in 1 .. Lastsc loop
                            if (not Scxclu (I)) then
                                Scbol (I) := Nfa.Mkbranch (Scbol (I), Pat);
                            end if;
                        end loop;

                        if (not Bol_Needed) then
                            Bol_Needed := True;

                            if (Performance_Report) then
                                Text_Io.Put
                                   (Standard_Error,
                                    "'^' operator results in sub-optimal performance");
                                Text_Io.New_Line (Standard_Error);
                            end if;
                        end if;


                    when 18 =>
--#line  188

                        Pat := Nfa.Link_Machines (Yy.Value_Stack (Yy.Tos - 1),
                                                  Yy.Value_Stack (Yy.Tos));
                        Nfa.Finish_Rule (Pat, Variable_Trail_Rule,
                                         Headcnt, Trailcnt);

                        for I in 1 .. Lastsc loop
                            if (not Scxclu (I)) then
                                Scset (I) := Nfa.Mkbranch (Scset (I), Pat);
                            end if;
                        end loop;


                    when 19 =>
--#line  201
                        Build_Eof_Action;

                    when 20 =>
--#line  204

                        -- this EOF applies only to the INITIAL start cond.
                        Actvp := 1;
                        Actvsc (Actvp) := 1;
                        Build_Eof_Action;


                    when 21 =>
--#line  212
                        Misc.Synerr ("unrecognized rule");

                    when 23 =>
--#line  219

                        Scnum := Sym.Sclookup (Nmstr);
                        if (Scnum = 0) then
                            Text_Io.Put (Standard_Error,
                                         "undeclared start condition ");
                            Tstring.Put (Standard_Error, Nmstr);
                            Main_Body.Aflexend (1);
                        else
                            Actvp := Actvp + 1;
                            Actvsc (Actvp) := Scnum;
                        end if;


                    when 24 =>
--#line  233

                        Scnum := Sym.Sclookup (Nmstr);
                        if (Scnum = 0) then
                            Text_Io.Put (Standard_Error,
                                         "undeclared start condition ");
                            Tstring.Put (Standard_Error, Nmstr);
                            Main_Body.Aflexend (1);
                        else
                            Actvp := 1;
                            Actvsc (Actvp) := Scnum;
                        end if;


                    when 25 =>
--#line  247
                        Misc.Synerr ("bad start condition list");

                    when 26 =>
--#line  251

                        if Trlcontxt then
                            Misc.Synerr ("trailing context used twice");

                            Yyval := Nfa.Mkstate (Sym_Epsilon);
                        else
                            Trlcontxt := True;

                            if (not Varlength) then
                                Headcnt := Rulelen;
                            end if;

                            Rulelen := Rulelen + 1;
                            Trailcnt := 1;

                            Eps := Nfa.Mkstate (Sym_Epsilon);

                            Yyval := Nfa.Link_Machines
                                        (Eps, Nfa.Mkstate
                                                 (Character'Pos (Ascii.Lf)));
                        end if;


                    when 27 =>
--#line  272


                        Yyval := Nfa.Mkstate (Sym_Epsilon);

                        if (Trlcontxt) then
                            if (Varlength and (Headcnt = 0)) then
                                -- both head and trail are variable-length
                                Variable_Trail_Rule := True;
                            else
                                Trailcnt := Rulelen;
                            end if;
                        end if;


                    when 28 =>
--#line  287

                        Varlength := True;


                        Yyval := Nfa.Mkor (Yy.Value_Stack (Yy.Tos - 2),
                                           Yy.Value_Stack (Yy.Tos));


                    when 29 =>
--#line  294

                        if (Transchar (Lastst (Yy.Value_Stack (Yy.Tos))) /=
                            Sym_Epsilon) then
                            -- provide final transition \now/ so it
                            -- will be marked as a trailing context
                            -- state


                            Yy.Value_Stack (Yy.Tos) :=
                               Nfa.Link_Machines (Yy.Value_Stack (Yy.Tos),
                                                  Nfa.Mkstate (Sym_Epsilon));
                        end if;

                        Nfa.Mark_Beginning_As_Normal (Yy.Value_Stack (Yy.Tos));
                        Current_State_Enum := State_Normal;

                        if (Previous_Continued_Action) then
                            -- we need to treat this as variable trailing
                            -- context so that the backup does not happen
                            -- in the action but before the action switch
                            -- statement.  If the backup happens in the
                            -- action, then the rules "falling into" this
                            -- one's action will *also* do the backup,
                            -- erroneously.
                            if ((not Varlength) or Headcnt /= 0) then
                                Text_Io.Put
                                   (Standard_Error,
                                    "alex: warning - trailing context rule at line");
                                Int_Io.Put (Standard_Error, Linenum);
                                Text_Io.Put
                                   (Standard_Error,
                                    "made variable because of preceding '|' action");
                                Int_Io.Put (Standard_Error, Linenum);
                            end if;

                            -- mark as variable
                            Varlength := True;
                            Headcnt := 0;
                        end if;

                        if (Varlength and (Headcnt = 0)) then
                            -- variable trailing context rule
                            -- mark the first part of the rule as the accepting
                            -- "head" part of a trailing context rule

                            -- by the way, we didn't do this at the beginning
                            -- of this production because back then
                            -- current_state_enum was set up for a trail
                            -- rule, and add_accept() can create a new
                            -- state ...

                            Nfa.Add_Accept
                               (Yy.Value_Stack (Yy.Tos - 1),
                                Misc.Set_Yy_Trailing_Head_Mask (Num_Rules));
                        end if;


                        Yyval := Nfa.Link_Machines (Yy.Value_Stack (Yy.Tos - 1),
                                                    Yy.Value_Stack (Yy.Tos));


                    when 30 =>
--#line  348

                        Yyval := Yy.Value_Stack (Yy.Tos);

                    when 31 =>
--#line  353

                        -- this rule is separate from the others for "re" so
                        -- that the reduction will occur before the trailing
                        -- series is parsed

                        if (Trlcontxt) then
                            Misc.Synerr ("trailing context used twice");
                        else
                            Trlcontxt := True;
                        end if;

                        if (Varlength) then
                            -- we hope the trailing context is fixed-length
                            Varlength := False;
                        else
                            Headcnt := Rulelen;
                        end if;

                        Rulelen := 0;

                        Current_State_Enum := State_Trailing_Context;

                        Yyval := Yy.Value_Stack (Yy.Tos - 1);


                    when 32 =>
--#line  379

                        -- this is where concatenation of adjacent patterns
                        -- gets done


                        Yyval := Nfa.Link_Machines (Yy.Value_Stack (Yy.Tos - 1),
                                                    Yy.Value_Stack (Yy.Tos));


                    when 33 =>
--#line  387

                        Yyval := Yy.Value_Stack (Yy.Tos);

                    when 34 =>
--#line  391

                        Varlength := True;


                        Yyval := Nfa.Mkclos (Yy.Value_Stack (Yy.Tos - 1));


                    when 35 =>
--#line  398

                        Varlength := True;


                        Yyval := Nfa.Mkposcl (Yy.Value_Stack (Yy.Tos - 1));


                    when 36 =>
--#line  405

                        Varlength := True;


                        Yyval := Nfa.Mkopt (Yy.Value_Stack (Yy.Tos - 1));


                    when 37 =>
--#line  412

                        Varlength := True;

                        if ((Yy.Value_Stack (Yy.Tos - 3) >
                             Yy.Value_Stack (Yy.Tos - 1)) or
                            (Yy.Value_Stack (Yy.Tos - 3) < 0)) then
                            Misc.Synerr ("bad iteration values");

                            Yyval := Yy.Value_Stack (Yy.Tos - 5);
                        else
                            if (Yy.Value_Stack (Yy.Tos - 3) = 0) then

                                Yyval := Nfa.Mkopt
                                            (Nfa.Mkrep (Yy.Value_Stack
                                                           (Yy.Tos - 5),
                                                        Yy.Value_Stack
                                                           (Yy.Tos - 3),
                                                        Yy.Value_Stack
                                                           (Yy.Tos - 1)));
                            else

                                Yyval := Nfa.Mkrep
                                            (Yy.Value_Stack (Yy.Tos - 5),
                                             Yy.Value_Stack (Yy.Tos - 3),
                                             Yy.Value_Stack (Yy.Tos - 1));
                            end if;
                        end if;


                    when 38 =>
--#line  428

                        Varlength := True;

                        if (Yy.Value_Stack (Yy.Tos - 2) <= 0) then
                            Misc.Synerr ("iteration value must be positive");

                            Yyval := Yy.Value_Stack (Yy.Tos - 4);
                        else

                            Yyval := Nfa.Mkrep
                                        (Yy.Value_Stack (Yy.Tos - 4),
                                         Yy.Value_Stack (Yy.Tos - 2), Infinity);
                        end if;


                    when 39 =>
--#line  440

                        -- the singleton could be something like "(foo)",
                        -- in which case we have no idea what its length
                        -- is, so we punt here.

                        Varlength := True;

                        if (Yy.Value_Stack (Yy.Tos - 1) <= 0) then
                            Misc.Synerr ("iteration value must be positive");

                            Yyval := Yy.Value_Stack (Yy.Tos - 3);
                        else

                            Yyval := Nfa.Link_Machines
                                        (Yy.Value_Stack (Yy.Tos - 3),
                                         Nfa.Copysingl
                                            (Yy.Value_Stack (Yy.Tos - 3),
                                             Yy.Value_Stack (Yy.Tos - 1) - 1));
                        end if;


                    when 40 =>
--#line  456

                        if (not Madeany) then
                            -- create the '.' character class
                            Anyccl := Ccl.Cclinit;
                            Ccl.Ccladd (Anyccl, Ascii.Lf);
                            Ccl.Cclnegate (Anyccl);

                            if (Useecs) then
                                Ecs.Mkeccl (Ccltbl (Cclmap (Anyccl) ..
                                                       Cclmap (Anyccl) +
                                                          Ccllen (Anyccl)),
                                            Ccllen (Anyccl), Nextecm,
                                            Ecgroup, Csize);
                            end if;
                            Madeany := True;
                        end if;

                        Rulelen := Rulelen + 1;


                        Yyval := Nfa.Mkstate (-Anyccl);


                    when 41 =>
--#line  478

                        if (not Cclsorted) then
                            -- sort characters for fast searching.  We use a
                            -- shell sort since this list could be large.

--\x09\x09\x09    misc.cshell( ccltbl + cclmap($1), ccllen($1) );
                            Misc.Cshell
                               (Ccltbl (Cclmap (Yy.Value_Stack (Yy.Tos)) ..
                                           Cclmap (Yy.Value_Stack (Yy.Tos)) +
                                              Ccllen (Yy.Value_Stack (Yy.Tos))),
                                Ccllen (Yy.Value_Stack (Yy.Tos)));
                        end if;

                        if (Useecs) then
                            Ecs.Mkeccl (Ccltbl
                                           (Cclmap (Yy.Value_Stack (Yy.Tos)) ..
                                               Cclmap (Yy.Value_Stack
                                                          (Yy.Tos)) +
                                               Ccllen (Yy.Value_Stack
                                                          (Yy.Tos))),
                                        Ccllen (Yy.Value_Stack (Yy.Tos)),
                                        Nextecm, Ecgroup, Csize);
                        end if;

                        Rulelen := Rulelen + 1;


                        Yyval := Nfa.Mkstate (-Yy.Value_Stack (Yy.Tos));


                    when 42 =>
--#line  499

                        Rulelen := Rulelen + 1;


                        Yyval := Nfa.Mkstate (-Yy.Value_Stack (Yy.Tos));


                    when 43 =>
--#line  506

                        Yyval := Yy.Value_Stack (Yy.Tos - 1);

                    when 44 =>
--#line  509

                        Yyval := Yy.Value_Stack (Yy.Tos - 1);

                    when 45 =>
--#line  512

                        Rulelen := Rulelen + 1;

                        if (Yy.Value_Stack (Yy.Tos) =
                            Character'Pos (Ascii.Nul)) then
                            Misc.Synerr ("null in rule");
                        end if;

                        if (Caseins and (Yy.Value_Stack (Yy.Tos) >=
                                         Character'Pos ('A')) and
                            (Yy.Value_Stack (Yy.Tos) <=
                             Character'Pos ('Z'))) then

                            Yy.Value_Stack (Yy.Tos) :=
                               Misc.Clower (Yy.Value_Stack (Yy.Tos));
                        end if;


                        Yyval := Nfa.Mkstate (Yy.Value_Stack (Yy.Tos));


                    when 46 =>
--#line  528

                        Yyval := Yy.Value_Stack (Yy.Tos - 1);

                    when 47 =>
--#line  531

                        -- *Sigh* - to be compatible Unix lex, negated ccls
                        -- match newlines
                        Ccl.Cclnegate (Yy.Value_Stack (Yy.Tos - 1));

                        Yyval := Yy.Value_Stack (Yy.Tos - 1);


                    when 48 =>
--#line  540

                        if (Yy.Value_Stack (Yy.Tos - 2) >
                            Yy.Value_Stack (Yy.Tos)) then
                            Misc.Synerr ("negative range in character class");
                        else
                            if (Caseins) then
                                if ((Yy.Value_Stack (Yy.Tos - 2) >=
                                     Character'Pos ('A')) and
                                    (Yy.Value_Stack (Yy.Tos - 2) <=
                                     Character'Pos ('Z'))) then

                                    Yy.Value_Stack (Yy.Tos - 2) :=
                                       Misc.Clower (Yy.Value_Stack
                                                       (Yy.Tos - 2));
                                end if;  
                                if ((Yy.Value_Stack (Yy.Tos) >=
                                     Character'Pos ('A')) and
                                    (Yy.Value_Stack (Yy.Tos) <=
                                     Character'Pos ('Z'))) then

                                    Yy.Value_Stack (Yy.Tos) :=
                                       Misc.Clower (Yy.Value_Stack (Yy.Tos));
                                end if;  
                            end if;

                            for I in Yy.Value_Stack (Yy.Tos - 2) ..
                                        Yy.Value_Stack (Yy.Tos) loop
                                Ccl.Ccladd (Yy.Value_Stack (Yy.Tos - 3),
                                            Character'Val (I));
                            end loop;

                            -- keep track if this ccl is staying in
                            -- alphabetical order

                            Cclsorted :=
                               Cclsorted and
                                  (Yy.Value_Stack (Yy.Tos - 2) > Lastchar);
                            Lastchar := Yy.Value_Stack (Yy.Tos);
                        end if;


                        Yyval := Yy.Value_Stack (Yy.Tos - 3);


                    when 49 =>
--#line  568

                        if (Caseins) then
                            if ((Yy.Value_Stack (Yy.Tos) >=
                                 Character'Pos ('A')) and
                                (Yy.Value_Stack (Yy.Tos) <=
                                 Character'Pos ('Z'))) then

                                Yy.Value_Stack (Yy.Tos) :=
                                   Misc.Clower (Yy.Value_Stack (Yy.Tos));
                            end if;
                        end if;  
                        Ccl.Ccladd (Yy.Value_Stack (Yy.Tos - 1),
                                    Character'Val (Yy.Value_Stack (Yy.Tos)));
                        Cclsorted := Cclsorted and
                                        (Yy.Value_Stack (Yy.Tos) > Lastchar);
                        Lastchar := Yy.Value_Stack (Yy.Tos);

                        Yyval := Yy.Value_Stack (Yy.Tos - 1);


                    when 50 =>
--#line  581

                        Cclsorted := True;
                        Lastchar := 0;

                        Yyval := Ccl.Cclinit;


                    when 51 =>
--#line  589

                        if (Caseins) then
                            if ((Yy.Value_Stack (Yy.Tos) >=
                                 Character'Pos ('A')) and
                                (Yy.Value_Stack (Yy.Tos) <=
                                 Character'Pos ('Z'))) then

                                Yy.Value_Stack (Yy.Tos) :=
                                   Misc.Clower (Yy.Value_Stack (Yy.Tos));
                            end if;
                        end if;

                        Rulelen := Rulelen + 1;


                        Yyval := Nfa.Link_Machines
                                    (Yy.Value_Stack (Yy.Tos - 1),
                                     Nfa.Mkstate (Yy.Value_Stack (Yy.Tos)));


                    when 52 =>
--#line  602

                        Yyval := Nfa.Mkstate (Sym_Epsilon);

                    when others =>
                        null;
                end case;

                -- Pop RHS states and goto next state
                Yy.Tos := Yy.Tos - Rule_Length (Yy.Rule_Id) + 1;
                Yy.State_Stack (Yy.Tos) := Goto_State
                                              (Yy.State_Stack (Yy.Tos - 1),
                                               Get_Lhs_Rule (Yy.Rule_Id));

                Yy.Value_Stack (Yy.Tos) := Yyval;

                if Yy.Debug then
                    Reduce_Debug (Yy.Rule_Id, Goto_State
                                                 (Yy.State_Stack (Yy.Tos - 1),
                                                  Get_Lhs_Rule (Yy.Rule_Id)));
                end if;

            end if;
        end loop;

    end Yyparse;
end Parser;

E3 Meta Data

    nblk1=25
    nid=0
    hdr6=4a
        [0x00] rec0=18 rec1=00 rec2=01 rec3=048
        [0x01] rec0=24 rec1=00 rec2=02 rec3=016
        [0x02] rec0=1c rec1=00 rec2=03 rec3=018
        [0x03] rec0=1d rec1=00 rec2=04 rec3=020
        [0x04] rec0=19 rec1=00 rec2=05 rec3=042
        [0x05] rec0=1c rec1=00 rec2=06 rec3=02c
        [0x06] rec0=19 rec1=00 rec2=07 rec3=012
        [0x07] rec0=17 rec1=00 rec2=08 rec3=02e
        [0x08] rec0=1f rec1=00 rec2=09 rec3=016
        [0x09] rec0=1b rec1=00 rec2=0a rec3=084
        [0x0a] rec0=1f rec1=00 rec2=0b rec3=026
        [0x0b] rec0=23 rec1=00 rec2=0c rec3=024
        [0x0c] rec0=1f rec1=00 rec2=0d rec3=008
        [0x0d] rec0=18 rec1=00 rec2=0e rec3=028
        [0x0e] rec0=16 rec1=00 rec2=0f rec3=018
        [0x0f] rec0=17 rec1=00 rec2=10 rec3=072
        [0x10] rec0=20 rec1=00 rec2=11 rec3=062
        [0x11] rec0=1b rec1=00 rec2=12 rec3=014
        [0x12] rec0=1f rec1=00 rec2=13 rec3=032
        [0x13] rec0=1c rec1=00 rec2=14 rec3=06e
        [0x14] rec0=14 rec1=00 rec2=15 rec3=000
        [0x15] rec0=13 rec1=00 rec2=16 rec3=098
        [0x16] rec0=1b rec1=00 rec2=17 rec3=03e
        [0x17] rec0=1b rec1=00 rec2=18 rec3=090
        [0x18] rec0=2d rec1=00 rec2=19 rec3=03a
        [0x19] rec0=13 rec1=00 rec2=1a rec3=022
        [0x1a] rec0=1c rec1=00 rec2=1b rec3=006
        [0x1b] rec0=18 rec1=00 rec2=1c rec3=056
        [0x1c] rec0=19 rec1=00 rec2=1d rec3=076
        [0x1d] rec0=12 rec1=00 rec2=1e rec3=016
        [0x1e] rec0=26 rec1=00 rec2=1f rec3=056
        [0x1f] rec0=20 rec1=00 rec2=20 rec3=010
        [0x20] rec0=12 rec1=00 rec2=21 rec3=01a
        [0x21] rec0=18 rec1=00 rec2=22 rec3=00a
        [0x22] rec0=18 rec1=00 rec2=23 rec3=000
        [0x23] rec0=20 rec1=00 rec2=24 rec3=00a
        [0x24] rec0=19 rec1=00 rec2=25 rec3=000
    tail 0x2172a407084a64e9b6c13 0x42a00088462060003