Browse Source

+ updated to version 4.1a

michael 25 years ago
parent
commit
a81c855602

+ 14 - 14
utils/tply/lexbase.pas

@@ -33,7 +33,7 @@ $Revision$
 $Modtime: 96-08-01 10:21 $
 
 $History: LEXBASE.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -51,11 +51,11 @@ const
 
 (* symbolic character constants: *)
 
-bs   = #8;      (* backspace character *)
-tab  = #9;      (* tab character *)
-nl   = #10;     (* newline character *)
-cr   = #13;     (* carriage return *)
-ff   = #12;     (* form feed character *)
+bs   = #8;	(* backspace character *)
+tab  = #9;	(* tab character *)
+nl   = #10;	(* newline character *)
+cr   = #13;	(* carriage return *)
+ff   = #12;	(* form feed character *)
 
 var
 
@@ -65,7 +65,7 @@ lfilename     : String;
 pasfilename   : String;
 lstfilename   : String;
 codfilename   : String;
-codfilepath   : String; { Under linux, binary and conf file
+codfilepath   : String; { Under linux, binary and conf file 
                           are not in the same path}
 
 (* Lex input, output, list and code template file: *)
@@ -1086,18 +1086,18 @@ function cclassStr(cc : CClass) : String;
         c1 := chr(0);
         Quit := False;
         while not Quit do  begin
-          if c1 in cc then  begin
-            c2 := c1;
-            while (c2<MaxChar) and (succ(c2) in cc) do
+	  if c1 in cc then  begin
+	    c2 := c1;
+	    while (c2<MaxChar) and (succ(c2) in cc) do
               c2 := succ(c2);
-            if c1=c2
+	    if c1=c2
              then  str := str+charStr(c1, reserved)
-             else
+	     else
                if c2=succ(c1)
                 then  str := str+charStr(c1, reserved)+charStr(c2, reserved)
-                else  str := str+charStr(c1, reserved)+'-'+charStr(c2, reserved);
+	        else  str := str+charStr(c1, reserved)+'-'+charStr(c2, reserved);
               c1 := c2;
-          end;
+	  end;
           Quit := c1 = MaxChar;
           if not Quit then
             c1 := Succ(c1);

+ 1 - 1
utils/tply/lexdfa.pas

@@ -26,7 +26,7 @@ $Revision$
 $Modtime: 96-08-01 6:13 $
 
 $History: LEXDFA.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply

+ 1 - 1
utils/tply/lexlib.pas

@@ -406,4 +406,4 @@ begin
   reset(yyinput); rewrite(yyoutput);
   yylineno := 0;
   yyclear;
-end(*LexLib*).
+end(*LexLib*).

+ 8 - 8
utils/tply/lexlist.pas

@@ -32,7 +32,7 @@ $Revision$
 $Modtime: 96-08-01 6:28 $
 
 $History: LEXLIST.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -75,16 +75,16 @@ procedure listPosTable;
     for p := 1 to n_pos do
       with pos_table^[p] do
         begin
-          write(yylst, p:5, '     ');
+	  write(yylst, p:5, '     ');
           if pos_type=char_pos then
             write(yylst, singleQuoteStr(c):20)
           else if pos_type=cclass_pos then
             write(yylst, cclassStr(cc^):20)
-          else if pos_type=mark_pos then
-            if pos=0 then
-              write(yylst, '# (rule '+intStr(rule)+')':20)
-            else
-              write(yylst, '/ (rule '+intStr(rule)+')':20);
+	  else if pos_type=mark_pos then
+	    if pos=0 then
+	      write(yylst, '# (rule '+intStr(rule)+')':20)
+	    else
+	      write(yylst, '/ (rule '+intStr(rule)+')':20);
           write(yylst, ' ':5);
           for i := 1 to size(follow_pos^) do
             if follow_pos^[i]>0 then write(yylst, follow_pos^[i]:5, ' ');
@@ -124,7 +124,7 @@ procedure listDFATable;
 {$else}
             for k := 1 to size(state_pos^) do
               with pos_table^[state_pos^[k]] do
-                if (pos_type=mark_pos) and (pos=0) then
+		if (pos_type=mark_pos) and (pos=0) then
                   write(yylst, ' ', rule:5);
 {$endif}
             writeln(yylst);

+ 15 - 15
utils/tply/lexmsgs.pas

@@ -27,7 +27,7 @@ $Revision$
 $Modtime: 96-08-01 8:52 $
 
 $History: LEXMSGS.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -56,7 +56,7 @@ const
 
 (* sign-on and usage message: *)
 
-sign_on = 'TP Lex Version 4.1 [May 1998], Copyright (c) 1990-98 Albert Graef';
+sign_on = 'TP Lex Version 4.1a [April 2000], Copyright (c) 1990-2000 Albert Graef';
 {$ifdef linux}
 usage   = 'Usage: plex [options] lex-file[.l] [output-file[.pas]]';
 {$else}
@@ -72,27 +72,27 @@ illegal_no_args                 = 'illegal number of parameters';
 (* syntax errors: *)
 
 unmatched_lbrace                = '101: unmatched %{';
-syntax_error                    = '102: syntax error';
+syntax_error 			= '102: syntax error';
 unexpected_eof                  = '103: unexpected end of file';
 
 (* semantic errors: *)
 
-symbol_already_defined          = '201: symbol already defined';
+symbol_already_defined 		= '201: symbol already defined';
 undefined_symbol                = '202: undefined symbol';
 invalid_charnum                 = '203: invalid character number';
-empty_grammar                   = '204: empty grammar?';
+empty_grammar 			= '204: empty grammar?';
 
 (* fatal errors: *)
 
-cannot_open_file                = 'FATAL: cannot open file ';
+cannot_open_file 		= 'FATAL: cannot open file ';
 write_error                     = 'FATAL: write error';
-mem_overflow                    = 'FATAL: memory overflow';
-intset_overflow                 = 'FATAL: integer set overflow';
-sym_table_overflow              = 'FATAL: symbol table overflow';
-pos_table_overflow              = 'FATAL: position table overflow';
-state_table_overflow            = 'FATAL: state table overflow';
-trans_table_overflow            = 'FATAL: transition table overflow';
-macro_stack_overflow            = 'FATAL: macro stack overflow';
+mem_overflow 			= 'FATAL: memory overflow';
+intset_overflow 		= 'FATAL: integer set overflow';
+sym_table_overflow 		= 'FATAL: symbol table overflow';
+pos_table_overflow 		= 'FATAL: position table overflow';
+state_table_overflow 		= 'FATAL: state table overflow';
+trans_table_overflow 		= 'FATAL: transition table overflow';
+macro_stack_overflow 		= 'FATAL: macro stack overflow';
 
 implementation
 
@@ -152,7 +152,7 @@ procedure fatal(msg : String);
 
 {$ifndef fpc}
 {$IFNDEF Win32}
-function heapErrorHandler ( size : Word ): Integer; {$ifndef fpc}far;{$endif}
+function heapErrorHandler ( size : Word ): Integer; far;
   begin
     if size>0 then
       fatal(mem_overflow) (* never returns *)
@@ -170,4 +170,4 @@ begin
   heapError := @heapErrorHandler;
 {$ENDIF}
 {$endif}
-end(*LexMsgs*).
+end(*LexMsgs*).

+ 6 - 4
utils/tply/lexopt.pas

@@ -26,7 +26,7 @@ $Revision$
 $Modtime: 96-08-01 6:29 $
 
 $History: LEXOPT.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -50,9 +50,11 @@ uses LexBase, LexTable;
 
 (* Partition table used in DFA optimization: *)
 
+(* obsolete
+
 const
 
-max_parts = max_states;  (* number of partitions of equivalent states; at
+max_parts = max_states;*)  (* number of partitions of equivalent states; at
                             worst, each state may be in a partition by
                             itself *)
 
@@ -152,8 +154,8 @@ procedure optimizeDFATable;
     part_table^[0] := newIntSet;
     for i := 0 to n_states-1 do
       begin
-        include(part_table^[0]^, i);
-        state_part^[i] := 0;
+	include(part_table^[0]^, i);
+	state_part^[i] := 0;
       end;
 
     (* Now, repeatedly pass over the created partitions, breaking up

+ 2 - 2
utils/tply/lexpos.pas

@@ -32,7 +32,7 @@ $Revision$
 $Modtime: 96-08-01 6:30 $
 
 $History: LEXPOS.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -163,4 +163,4 @@ procedure addExpr(r : RegExpr; var FIRST : IntSet);
     eval(r, FIRST, LAST, nullable);
   end(*addExpr*);
 
-end(*LexPos*).
+end(*LexPos*).

+ 28 - 28
utils/tply/lexrules.pas

@@ -30,7 +30,7 @@ $Revision$
 $Modtime: 96-08-01 6:30 $
 
 $History: LEXRULES.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -265,37 +265,37 @@ procedure parse_rule ( rule_no : Integer );
 
     (* parse rule according to syntax:
 
-       rule                     : start_state_prefix caret
-                                  expr [ '$' | '/' expr ]
-                                ;
+       rule			: start_state_prefix caret
+				  expr [ '$' | '/' expr ]
+				;
 
-       start_state_prefix       : /* empty */
-                                | '<' start_state_list '>'
-                                ;
+       start_state_prefix	: /* empty */
+				| '<' start_state_list '>'
+				;
 
        start_state_list         : ident { ',' ident }
                                 ;
 
-       caret                    : /* empty */
-                                | '^'
-                                ;
-
-       expr                     : term { '|' term }
-                                ;
-
-       term                     : factor { factor }
-                                ;
-
-       factor                   : char
-                                | string
-                                | cclass
-                                | '.'
-                                | '(' expr ')'
-                                | factor '*'
-                                | factor '+'
-                                | factor '?'
-                                | factor '{' num [ ',' num ] '}'
-                                ;
+       caret			: /* empty */
+				| '^'
+				;
+
+       expr			: term { '|' term }
+				;
+
+       term			: factor { factor }
+				;
+
+       factor			: char
+				| string
+				| cclass
+				| '.'
+				| '(' expr ')'
+				| factor '*'
+				| factor '+'
+				| factor '?'
+				| factor '{' num [ ',' num ] '}'
+				;
     *)
 
     procedure start_state_prefix ( var done : Boolean );
@@ -623,4 +623,4 @@ procedure parse_rule ( rule_no : Integer );
       mark_error(syntax_error, 0)
   end(*parse_rule*);
 
-end(*LexRules*).
+end(*LexRules*).

+ 10 - 4
utils/tply/lextable.pas

@@ -29,7 +29,7 @@ $Revision$
 $Modtime: 96-08-01 10:23 $
 
 $History: LEXTABLE.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -371,13 +371,17 @@ procedure addTrans(cc : CClass; FOLLOW : IntSetPtr);
   end(*addCharTrans*);
 
 (* comparison and swap procedures for sorting transitions: *)
-function transLessNextState(i, j : Integer) : Boolean;{$ifndef fpc}far;{$endif}
+{$ifndef fpc}{$F+}{$endif}
+function transLessNextState(i, j : Integer) : Boolean;
+{$ifndef fpc}{$F-}{$endif}
   (* compare transitions based on next states (used in mergeCharTrans) *)
   begin
     transLessNextState := trans_table^[i].next_state<
                           trans_table^[j].next_state
   end(*transLessNextState*);
-function transLess(i, j : Integer) : Boolean;{$ifndef fpc}far;{$endif}
+{$ifndef fpc}{$F+}{$endif}
+function transLess(i, j : Integer) : Boolean;
+{$ifndef fpc}{$F-}{$endif}
   (* lexical order on transitions *)
   var c : Char; xi, xj : Boolean;
   begin
@@ -393,7 +397,9 @@ function transLess(i, j : Integer) : Boolean;{$ifndef fpc}far;{$endif}
       end;
     transLess := false
   end(*transLess*);
-procedure transSwap(i, j : Integer);{$ifndef fpc}far;{$endif}
+{$ifndef fpc}{$F+}{$endif}
+procedure transSwap(i, j : Integer);
+{$ifndef fpc}{$F-}{$endif}
   (* swap transitions i and j *)
   var x : TransTableEntry;
   begin

+ 29 - 27
utils/tply/plex.pas

@@ -24,7 +24,7 @@ $Revision$
 $Modtime: 96-08-01 10:22 $
 
 $History: LEX.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -135,7 +135,7 @@ procedure define_macro ( symbol, replacement : String );
       if sym_type=none then
         begin
           sym_type := macro_sym;
-          subst    := newStr(replacement);
+          subst    := newStr(strip(replacement));
         end
       else
         error(symbol_already_defined, 1)
@@ -259,30 +259,30 @@ procedure generate_table;
       while not Quit do begin
         if c1 in cc then  begin
           if col>0 then
-            begin
-              write(f, ',');
-              inc(col);
-            end;
-          if col>40 then
-            { insert line break }
-            begin
-              writeln(f);
-              write(f, ' ':12);
-              col := 0;
-            end;
-          c2 := c1;
-          while (c2<MaxChar) and (succ(c2) in cc) do
-            c2 := succ(c2);
-          if c1=c2 then
-            tag := charStr(c1)
-          else if c2=succ(c1) then
-            tag := charStr(c1)+','+charStr(c2)
-          else
-            tag := charStr(c1)+'..'+charStr(c2);
-          write(f, tag);
-          col := col + length(tag);
+	    begin
+	      write(f, ',');
+	      inc(col);
+	    end;
+	  if col>40 then
+	    { insert line break }
+	    begin
+	      writeln(f);
+	      write(f, ' ':12);
+	      col := 0;
+	    end;
+	  c2 := c1;
+	  while (c2<MaxChar) and (succ(c2) in cc) do
+	    c2 := succ(c2);
+	  if c1=c2 then
+	    tag := charStr(c1)
+	  else if c2=succ(c1) then
+	    tag := charStr(c1)+','+charStr(c2)
+	  else
+	    tag := charStr(c1)+'..'+charStr(c2);
+	  write(f, tag);
+	  col := col + length(tag);
           c1 := c2;
-        end;
+	end;
         Quit := c1 = MaxChar;
         if not Quit then
           c1 := Succ(c1);
@@ -514,7 +514,7 @@ procedure definitions;
           end
       end(*check_id*);
     var i : Integer;
-        com : String;
+	com : String;
     begin
       split(line, 2);
       com := upper(itemv(1));
@@ -728,9 +728,11 @@ begin
 
   if warnings>0 then writeln(warnings, ' warnings.');
 
+{$ifndef fpc}
 {$IFNDEF Win32}
   writeln( n_bytes, '/', max_bytes, ' bytes of memory used.');
 {$ENDIF}
+{$endif}
 
   (* terminate: *)
 
@@ -742,4 +744,4 @@ begin
 
   halt(errors);
 
-end(*Lex*).
+end(*Lex*).

+ 76 - 74
utils/tply/pyacc.pas

@@ -36,7 +36,7 @@ Last changes:
     updates)
 
 $History: YACC.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -175,28 +175,28 @@ begin
          yyval := yyv[yysp-0];
        end;
    6 : begin
-         yyerrok;
+         yyerrok; 
        end;
    7 : begin
-         yyerrok;
+         yyerrok; 
        end;
    8 : begin
-         yyerrok;
+         yyerrok; 
        end;
    9 : begin
-         yyerrok;
+         yyerrok; 
        end;
   10 : begin
-         yyerrok;
+         yyerrok; 
        end;
   11 : begin
-         yyerrok;
+         yyerrok; 
        end;
   12 : begin
          yyval := yyv[yysp-0];
        end;
   13 : begin
-         yyerrok;
+         yyerrok; 
        end;
   14 : begin
          yyval := yyv[yysp-0];
@@ -205,19 +205,19 @@ begin
          yyval := yyv[yysp-0];
        end;
   16 : begin
-         error(rcurl_expected);
+         error(rcurl_expected); 
        end;
   17 : begin
          yyval := yyv[yysp-0];
        end;
   18 : begin
-         yyerrok;
+         yyerrok; 
        end;
   19 : begin
-         yyerrok;
+         yyerrok; 
        end;
   20 : begin
-         yyerrok;
+         yyerrok; 
        end;
   21 : begin
          yyval := yyv[yysp-0];
@@ -226,7 +226,7 @@ begin
          yyval := yyv[yysp-0];
        end;
   23 : begin
-         error(rbrace_expected);
+         error(rbrace_expected); 
        end;
   24 : begin
          yyval := yyv[yysp-0];
@@ -235,7 +235,7 @@ begin
          yyval := yyv[yysp-0];
        end;
   26 : begin
-         error(rangle_expected);
+         error(rangle_expected); 
        end;
   27 : begin
          yyval := yyv[yysp-0];
@@ -243,12 +243,12 @@ begin
   28 : begin
          sort_types;
          definitions;
-         next_section;
+         next_section; 
        end;
   29 : begin
          next_section;
          generate_parser;
-         next_section;
+         next_section; 
        end;
   30 : begin
          yyval := yyv[yysp-5];
@@ -256,48 +256,48 @@ begin
   31 : begin
        end;
   32 : begin
-         copy_rest_of_file;
+         copy_rest_of_file; 
        end;
   33 : begin
        end;
   34 : begin
-         yyerrok;
+         yyerrok; 
        end;
   35 : begin
-         error(error_in_def);
+         error(error_in_def); 
        end;
   36 : begin
-         startnt := ntsym(yyv[yysp-0]);
+         startnt := ntsym(yyv[yysp-0]); 
        end;
   37 : begin
-         error(ident_expected);
+         error(ident_expected); 
        end;
   38 : begin
-         copy_code;
+         copy_code; 
        end;
   39 : begin
          yyval := yyv[yysp-2];
        end;
   40 : begin
-         act_prec := 0;
+         act_prec := 0; 
        end;
   41 : begin
          yyval := yyv[yysp-3];
        end;
   42 : begin
-         act_prec := new_prec_level(left);
+         act_prec := new_prec_level(left); 
        end;
   43 : begin
          yyval := yyv[yysp-3];
        end;
   44 : begin
-         act_prec := new_prec_level(right);
+         act_prec := new_prec_level(right); 
        end;
   45 : begin
          yyval := yyv[yysp-3];
        end;
   46 : begin
-         act_prec := new_prec_level(nonassoc);
+         act_prec := new_prec_level(nonassoc); 
        end;
   47 : begin
          yyval := yyv[yysp-3];
@@ -309,169 +309,169 @@ begin
          yyval := yyv[yysp-1];
        end;
   50 : begin
-         act_type := 0;
+         act_type := 0; 
        end;
   51 : begin
-         act_type := yyv[yysp-1]; add_type(yyv[yysp-1]);
+         act_type := yyv[yysp-1]; add_type(yyv[yysp-1]); 
        end;
   52 : begin
          yyval := yyv[yysp-0];
        end;
   53 : begin
-         yyerrok;
+         yyerrok; 
        end;
   54 : begin
-         yyerrok;
+         yyerrok; 
        end;
   55 : begin
-         error(ident_expected);
+         error(ident_expected); 
        end;
   56 : begin
-         error(error_in_def);
+         error(error_in_def); 
        end;
   57 : begin
-         error(ident_expected);
+         error(ident_expected); 
        end;
   58 : begin
          if act_type<>0 then
          sym_type^[yyv[yysp-0]] := act_type;
          if act_prec<>0 then
-         sym_prec^[yyv[yysp-0]] := act_prec;
+         sym_prec^[yyv[yysp-0]] := act_prec; 
        end;
   59 : begin
          litsym(yyv[yysp-0], 0);
          if act_type<>0 then
          sym_type^[litsym(yyv[yysp-0], 0)] := act_type;
          if act_prec<>0 then
-         sym_prec^[litsym(yyv[yysp-0], 0)] := act_prec;
+         sym_prec^[litsym(yyv[yysp-0], 0)] := act_prec; 
        end;
   60 : begin
          litsym(yyv[yysp-0], 0);
          if act_type<>0 then
          sym_type^[litsym(yyv[yysp-0], 0)] := act_type;
          if act_prec<>0 then
-         sym_prec^[litsym(yyv[yysp-0], 0)] := act_prec;
+         sym_prec^[litsym(yyv[yysp-0], 0)] := act_prec; 
        end;
   61 : begin
          litsym(yyv[yysp-1], 0);
          if act_type<>0 then
          sym_type^[litsym(yyv[yysp-1], yyv[yysp-0])] := act_type;
          if act_prec<>0 then
-         sym_prec^[litsym(yyv[yysp-1], 0)]  := act_prec;
+         sym_prec^[litsym(yyv[yysp-1], 0)]  := act_prec; 
        end;
   62 : begin
          litsym(yyv[yysp-1], 0);
          if act_type<>0 then
          sym_type^[litsym(yyv[yysp-1], yyv[yysp-0])] := act_type;
          if act_prec<>0 then
-         sym_prec^[litsym(yyv[yysp-1], 0)]  := act_prec;
+         sym_prec^[litsym(yyv[yysp-1], 0)]  := act_prec; 
        end;
   63 : begin
          yyval := yyv[yysp-0];
        end;
   64 : begin
-         yyerrok;
+         yyerrok; 
        end;
   65 : begin
-         yyerrok;
+         yyerrok; 
        end;
   66 : begin
-         error(ident_expected);
+         error(ident_expected); 
        end;
   67 : begin
-         error(error_in_def);
+         error(error_in_def); 
        end;
   68 : begin
-         error(ident_expected);
+         error(ident_expected); 
        end;
   69 : begin
          if act_type<>0 then
-         sym_type^[ntsym(yyv[yysp-0])] := act_type;
+         sym_type^[ntsym(yyv[yysp-0])] := act_type; 
        end;
   70 : begin
-         next_section;
+         next_section; 
        end;
   71 : begin
          yyval := yyv[yysp-1];
        end;
   72 : begin
-         copy_code;
+         copy_code; 
        end;
   73 : begin
-         next_section;
+         next_section; 
        end;
   74 : begin
          yyval := yyv[yysp-4];
        end;
   75 : begin
-         yyerrok;
+         yyerrok; 
        end;
   76 : begin
-         error(error_in_rule);
+         error(error_in_rule); 
        end;
   77 : begin
-         error(error_in_rule);
+         error(error_in_rule); 
        end;
   78 : begin
-         start_rule(ntsym(yyv[yysp-0]));
+         start_rule(ntsym(yyv[yysp-0])); 
        end;
   79 : begin
-         start_body;
+         start_body; 
        end;
   80 : begin
-         end_body;
+         end_body; 
        end;
   81 : begin
          yyval := yyv[yysp-0];
        end;
   82 : begin
-         start_body;
+         start_body; 
        end;
   83 : begin
-         end_body;
+         end_body; 
        end;
   84 : begin
        end;
   85 : begin
-         add_symbol(yyv[yysp-0]); yyerrok;
+         add_symbol(yyv[yysp-0]); yyerrok; 
        end;
   86 : begin
-         add_symbol(sym(yyv[yysp-0])); yyerrok;
+         add_symbol(sym(yyv[yysp-0])); yyerrok; 
        end;
   87 : begin
-         add_symbol(sym(yyv[yysp-0])); yyerrok;
+         add_symbol(sym(yyv[yysp-0])); yyerrok; 
        end;
   88 : begin
-         add_action; yyerrok;
+         add_action; yyerrok; 
        end;
   89 : begin
-         error(error_in_rule);
+         error(error_in_rule); 
        end;
   90 : begin
-         copy_action;
+         copy_action; 
        end;
   91 : begin
          yyval := yyv[yysp-2];
        end;
   92 : begin
-         copy_single_action;
+         copy_single_action; 
        end;
   93 : begin
        end;
   94 : begin
-         add_rule_prec(yyv[yysp-0]);
+         add_rule_prec(yyv[yysp-0]); 
        end;
   95 : begin
          yyval := yyv[yysp-3];
        end;
   96 : begin
-         add_rule_prec(litsym(yyv[yysp-0], 0));
+         add_rule_prec(litsym(yyv[yysp-0], 0)); 
        end;
   97 : begin
          yyval := yyv[yysp-3];
        end;
   98 : begin
-         add_rule_prec(litsym(yyv[yysp-0], 0));
+         add_rule_prec(litsym(yyv[yysp-0], 0)); 
        end;
   99 : begin
          yyval := yyv[yysp-3];
@@ -482,7 +482,7 @@ begin
  101 : begin
        end;
  102 : begin
-         add_action;
+         add_action; 
        end;
   end;
 end(*yyaction*);
@@ -2145,10 +2145,10 @@ function yylex : integer;
             ('0'<=line[cno]) and (line[cno]<='9') or
             (line[cno]='_') or
             (line[cno]='.') ) do
-        begin
-          idstr := idstr+line[cno];
-          inc(cno)
-        end;
+	begin
+	  idstr := idstr+line[cno];
+	  inc(cno)
+	end;
       yylval := get_key(idstr);
       scan;
       if not end_of_input and (line[cno]=':') then
@@ -2366,9 +2366,9 @@ function yylex : integer;
     else
       case line[cno] of
         'A'..'Z', 'a'..'z', '_' : yylex := scan_ident;
-        '''', '"' : yylex := scan_literal;
-        '0'..'9' : yylex := scan_num;
-        '%', '\' : yylex := scan_keyword;
+	'''', '"' : yylex := scan_literal;
+	'0'..'9' : yylex := scan_num;
+	'%', '\' : yylex := scan_keyword;
         '=' :
           if (cno<length(line)) and (line[succ(cno)]='{') then
             begin
@@ -2377,7 +2377,7 @@ function yylex : integer;
             end
           else
             yylex := scan_char;
-        else yylex := scan_char;
+	else yylex := scan_char;
       end;
     if lno=lno0 then
       tokleng := cno-cno0
@@ -2508,9 +2508,11 @@ begin
 
   if warnings>0 then writeln(warnings, ' warnings.');
 
+{$ifndef fpc}
 {$IFNDEF Win32}
   writeln( n_bytes, '/', max_bytes, ' bytes of memory used.');
 {$ENDIF}
+{$endif}
 
   (* terminate: *)
 

+ 194 - 192
utils/tply/pyacc.y

@@ -66,7 +66,7 @@ Last changes:
     updates)
 
 $History: YACC.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -161,20 +161,20 @@ uses
 /* Lexical part of the Yacc language: */
 
 %token
-  ID            /* identifiers: {letter}{letter_or_digit}* */
-  C_ID          /* identifier which forms left side of rule, i.e. is
-                   followed by a colon */
+  ID		/* identifiers: {letter}{letter_or_digit}* */
+  C_ID		/* identifier which forms left side of rule, i.e. is
+		   followed by a colon */
   LITERAL       /* single character literal */
   LITID         /* multiple character literal */
-  NUMBER        /* nonnegative integers: {digit}+ */
+  NUMBER	/* nonnegative integers: {digit}+ */
   PTOKEN PLEFT PRIGHT PNONASSOC PTYPE PSTART PPREC
-                /* reserved words: PTOKEN=%token, etc. */
-  PP            /* source sections separator %% */
-  LCURL         /* curly braces: %{ and %} */
+  		/* reserved words: PTOKEN=%token, etc. */
+  PP		/* source sections separator %% */
+  LCURL		/* curly braces: %{ and %} */
   RCURL
   ',' ':' ';' '|' '{' '}' '<' '>' '='
-                /* literals */
-  ILLEGAL       /* illegal input character */
+		/* literals */
+  ILLEGAL	/* illegal input character */
 
 %start grammar
 
@@ -183,234 +183,234 @@ uses
 /* Lexical entities, those that may give rise to syntax errors are augmented
    with error productions, and important symbols call yyerrok. */
 
-id              : ID
-c_id            : C_ID
+id		: ID
+c_id		: C_ID
 literal         : LITERAL
 litid           : LITID
-number          : NUMBER
-ptoken          : PTOKEN        { yyerrok; }
-pleft           : PLEFT         { yyerrok; }
-pright          : PRIGHT        { yyerrok; }
-pnonassoc       : PNONASSOC     { yyerrok; }
-ptype           : PTYPE         { yyerrok; }
-pstart          : PSTART        { yyerrok; }
-pprec           : PPREC
-pp              : PP            { yyerrok; }
-lcurl           : LCURL
-rcurl           : RCURL
-                | error         { error(rcurl_expected); }
-comma           : ','
-colon           : ':'           { yyerrok; }
-semicolon       : ';'           { yyerrok; }
-bar             : '|'           { yyerrok; }
-lbrace          : '{'
-rbrace          : '}'
-                | error         { error(rbrace_expected); }
-langle          : '<'
-rangle          : '>'
-                | error         { error(rangle_expected); }
-eq              : '='
+number		: NUMBER
+ptoken		: PTOKEN        { yyerrok; }
+pleft		: PLEFT	        { yyerrok; }
+pright		: PRIGHT        { yyerrok; }
+pnonassoc	: PNONASSOC	{ yyerrok; }
+ptype		: PTYPE	        { yyerrok; }
+pstart		: PSTART        { yyerrok; }
+pprec		: PPREC
+pp		: PP	        { yyerrok; }
+lcurl		: LCURL
+rcurl		: RCURL
+		| error	        { error(rcurl_expected); }
+comma		: ','
+colon		: ':'	        { yyerrok; }
+semicolon	: ';'	        { yyerrok; }
+bar		: '|'	        { yyerrok; }
+lbrace		: '{'
+rbrace		: '}'
+		| error	        { error(rbrace_expected); }
+langle		: '<'
+rangle		: '>'
+		| error         { error(rangle_expected); }
+eq		: '='
 
 /* Syntax and semantic routines: */
 
-grammar         : defs pp
-                                { sort_types;
+grammar		: defs pp
+		  		{ sort_types;
                                   definitions;
                                   next_section; }
-                  rules
-                                { next_section;
+		  rules
+		  		{ next_section;
                                   generate_parser;
                                   next_section; }
-                  aux_procs
-                ;
+		  aux_procs
+		;
 
-aux_procs       : /* empty: aux_procs is optional */
+aux_procs	: /* empty: aux_procs is optional */
 
-                | pp { copy_rest_of_file; }
+		| pp { copy_rest_of_file; }
 
-                ;
+		;
 
 
-defs            : /* empty */
-                | defs def      { yyerrok; }
-                | defs error    { error(error_in_def); }
-                ;
+defs		: /* empty */
+		| defs def	{ yyerrok; }
+		| defs error	{ error(error_in_def); }
+		;
 
-def             : pstart id
-                                { startnt := ntsym($2); }
-                | pstart error
-                                { error(ident_expected); }
-                | lcurl { copy_code; } rcurl
+def		: pstart id
+			 	{ startnt := ntsym($2); }
+		| pstart error
+				{ error(ident_expected); }
+		| lcurl { copy_code; } rcurl
 
-                | ptoken
-                                { act_prec := 0; }
-                  tag token_list
+		| ptoken
+				{ act_prec := 0; }
+		  tag token_list
 
-                | pleft
-                                { act_prec := new_prec_level(left); }
-                  tag token_list
+		| pleft
+				{ act_prec := new_prec_level(left); }
+		  tag token_list
 
-                | pright
-                                { act_prec := new_prec_level(right); }
-                  tag token_list
+		| pright
+				{ act_prec := new_prec_level(right); }
+		  tag token_list
 
-                | pnonassoc
-                                { act_prec := new_prec_level(nonassoc); }
-                  tag token_list
+		| pnonassoc
+				{ act_prec := new_prec_level(nonassoc); }
+		  tag token_list
 
-                | ptype tag nonterm_list
+		| ptype tag nonterm_list
 
                 | ptype tag
 
-                ;
-
-tag             : /* empty: type tag is optional */
-                                { act_type := 0; }
-                | langle id rangle
-                                { act_type := $2; add_type($2); }
-                ;
-
-token_list      : token_num
-
-                | token_list token_num
-                                { yyerrok; }
-                | token_list comma token_num
-                                { yyerrok; }
-                | error
-                                { error(ident_expected); }
-                | token_list error
-                                { error(error_in_def); }
-                | token_list comma error
-                                { error(ident_expected); }
-                ;
-
-token_num       : literal
-                                { if act_type<>0 then
+		;
+
+tag		: /* empty: type tag is optional */
+				{ act_type := 0; }
+		| langle id rangle
+				{ act_type := $2; add_type($2); }
+		;
+
+token_list	: token_num
+
+		| token_list token_num
+				{ yyerrok; }
+		| token_list comma token_num
+				{ yyerrok; }
+		| error
+				{ error(ident_expected); }
+		| token_list error
+				{ error(error_in_def); }
+		| token_list comma error
+				{ error(ident_expected); }
+		;
+
+token_num	: literal
+				{ if act_type<>0 then
                                     sym_type^[$1] := act_type;
                                   if act_prec<>0 then
                                     sym_prec^[$1] := act_prec; }
-                | litid
-                                { litsym($1, 0);
+               	| litid
+				{ litsym($1, 0);
                                   if act_type<>0 then
                                     sym_type^[litsym($1, 0)] := act_type;
                                   if act_prec<>0 then
                                     sym_prec^[litsym($1, 0)] := act_prec; }
-                | id
-                                { litsym($1, 0);
+               	| id
+				{ litsym($1, 0);
                                   if act_type<>0 then
                                     sym_type^[litsym($1, 0)] := act_type;
                                   if act_prec<>0 then
                                     sym_prec^[litsym($1, 0)] := act_prec; }
-                | litid number
-                                { litsym($1, 0);
+               	| litid number
+				{ litsym($1, 0);
                                   if act_type<>0 then
                                     sym_type^[litsym($1, $2)] := act_type;
                                   if act_prec<>0 then
                                     sym_prec^[litsym($1, 0)]  := act_prec; }
-                | id number
-                                { litsym($1, 0);
+               	| id number
+				{ litsym($1, 0);
                                   if act_type<>0 then
                                     sym_type^[litsym($1, $2)] := act_type;
                                   if act_prec<>0 then
                                     sym_prec^[litsym($1, 0)]  := act_prec; }
-                ;
-
-nonterm_list    : nonterm
-                | nonterm_list nonterm
-                                { yyerrok; }
-                | nonterm_list comma nonterm
-                                { yyerrok; }
-                | error
-                                { error(ident_expected); }
-                | nonterm_list error
-                                { error(error_in_def); }
-                | nonterm_list comma error
-                                { error(ident_expected); }
-                ;
-
-nonterm         : id
-                                { if act_type<>0 then
+		;
+
+nonterm_list	: nonterm
+		| nonterm_list nonterm
+				{ yyerrok; }
+		| nonterm_list comma nonterm
+				{ yyerrok; }
+		| error
+				{ error(ident_expected); }
+		| nonterm_list error
+				{ error(error_in_def); }
+		| nonterm_list comma error
+				{ error(ident_expected); }
+		;
+
+nonterm		: id
+				{ if act_type<>0 then
                                     sym_type^[ntsym($1)] := act_type; }
-                ;
-
-
-rules           :               { next_section; }
-                  rule1
-
-                | lcurl { copy_code; } rcurl
-                                { next_section; }
-                  rule1
-                                        /* rules section may be prefixed
-                                           with `local' Turbo Pascal
-                                           declarations */
-                | rules rule
-                                { yyerrok; }
-                | error
-                                { error(error_in_rule); }
-                | rules error
-                                { error(error_in_rule); }
-                ;
-
-rule1           : c_id
-                                { start_rule(ntsym($1)); }
-                  colon
-                                { start_body; }
-                  body prec
-                                { end_body; }
-                ;
-
-rule            : rule1
-
-                | bar
-                                { start_body; }
-                  body prec
-                                { end_body; }
-                ;
-
-body            : /* empty */
-
-                | body literal
-                                { add_symbol($2); yyerrok; }
-                | body litid
-                                { add_symbol(sym($2)); yyerrok; }
-                | body id
-                                { add_symbol(sym($2)); yyerrok; }
+		;
+
+
+rules		: 		{ next_section; }
+		  rule1
+
+		| lcurl { copy_code; } rcurl
+				{ next_section; }
+		  rule1
+					/* rules section may be prefixed
+					   with `local' Turbo Pascal
+					   declarations */
+		| rules rule
+				{ yyerrok; }
+		| error
+				{ error(error_in_rule); }
+		| rules error
+				{ error(error_in_rule); }
+		;
+
+rule1		: c_id
+				{ start_rule(ntsym($1)); }
+		  colon
+		  		{ start_body; }
+		  body prec
+				{ end_body; }
+		;
+
+rule		: rule1
+
+		| bar
+				{ start_body; }
+		  body prec
+				{ end_body; }
+		;
+
+body		: /* empty */
+
+		| body literal
+				{ add_symbol($2); yyerrok; }
+		| body litid
+				{ add_symbol(sym($2)); yyerrok; }
+		| body id
+				{ add_symbol(sym($2)); yyerrok; }
                 | body action
-                                { add_action; yyerrok; }
-                | body error
-                                { error(error_in_rule); }
-                ;
+				{ add_action; yyerrok; }
+		| body error
+				{ error(error_in_rule); }
+		;
 
-action          : lbrace { copy_action; } rbrace
+action		: lbrace { copy_action; } rbrace
 
-                | eq { copy_single_action; }
-                                /* old language feature; code must be
-                                   single statement ending with `;' */
-                ;
+		| eq { copy_single_action; }
+                		/* old language feature; code must be
+				   single statement ending with `;' */
+		;
 
-prec            : /* empty */
+prec		: /* empty */
 
-                | pprec literal
-                                { add_rule_prec($2); }
-                  opt_action
+		| pprec literal
+				{ add_rule_prec($2); }
+		  opt_action
 
-                | pprec litid
-                                { add_rule_prec(litsym($2, 0)); }
-                  opt_action
+		| pprec litid
+				{ add_rule_prec(litsym($2, 0)); }
+		  opt_action
 
-                | pprec id
-                                { add_rule_prec(litsym($2, 0)); }
-                  opt_action
+		| pprec id
+				{ add_rule_prec(litsym($2, 0)); }
+		  opt_action
 
-                | prec semicolon
+		| prec semicolon
 
-                ;
+		;
 
-opt_action      : /* empty */
+opt_action	: /* empty */
 
-                | action
-                                { add_action; }
-                ;
+		| action
+				{ add_action; }
+		;
 
 
 %%
@@ -481,10 +481,10 @@ function yylex : integer;
             ('0'<=line[cno]) and (line[cno]<='9') or
             (line[cno]='_') or
             (line[cno]='.') ) do
-        begin
-          idstr := idstr+line[cno];
-          inc(cno)
-        end;
+	begin
+	  idstr := idstr+line[cno];
+	  inc(cno)
+	end;
       yylval := get_key(idstr);
       scan;
       if not end_of_input and (line[cno]=':') then
@@ -702,9 +702,9 @@ function yylex : integer;
     else
       case line[cno] of
         'A'..'Z', 'a'..'z', '_' : yylex := scan_ident;
-        '''', '"' : yylex := scan_literal;
-        '0'..'9' : yylex := scan_num;
-        '%', '\' : yylex := scan_keyword;
+	'''', '"' : yylex := scan_literal;
+	'0'..'9' : yylex := scan_num;
+	'%', '\' : yylex := scan_keyword;
         '=' :
           if (cno<length(line)) and (line[succ(cno)]='{') then
             begin
@@ -713,7 +713,7 @@ function yylex : integer;
             end
           else
             yylex := scan_char;
-        else yylex := scan_char;
+	else yylex := scan_char;
       end;
     if lno=lno0 then
       tokleng := cno-cno0
@@ -844,9 +844,11 @@ begin
 
   if warnings>0 then writeln(warnings, ' warnings.');
 
+{$ifndef fpc}
 {$IFNDEF Win32}
   writeln( n_bytes, '/', max_bytes, ' bytes of memory used.');
 {$ENDIF}
+{$endif}
 
   (* terminate: *)
 

+ 2 - 2
utils/tply/tply.doc

@@ -42,7 +42,7 @@ are available from the TPLY homepage:
 
 For information about the Free Pascal Compiler, please refer to:
 
-   http://tfdec1.fys.kuleuven.ac.be/~michael/fpc/fpc.html
+   http://www.freepascal.org
 
 TP Lex and Yacc, like any other tools of this kind, are not intended for
 novices or casual programmers; they require extensive programming experience
@@ -1541,4 +1541,4 @@ Major differences between TP Yacc and UNIX Yacc are listed below.
   Yacc), and, of course, all macros of UNIX Yacc (YYERROR, YYACCEPT, etc.)
   had to be implemented as procedures.
 
-
+

+ 2 - 2
utils/tply/tply.tex

@@ -60,7 +60,7 @@ are available from the TPLY homepage:
 \end{verbatim}\end{quote}
 For information about the Free Pascal Compiler, please refer to:
 \begin{quote}\begin{verbatim}
-   http://tfdec1.fys.kuleuven.ac.be/~michael/fpc/fpc.html
+   http://www.freepascal.org
 \end{verbatim}\end{quote}
 
 TP Lex and Yacc, like any other tools of this kind, are not intended for
@@ -1639,4 +1639,4 @@ Major differences between TP Yacc and UNIX Yacc are listed below.
       procedures.
 \end{itemize}
 
-\end{document}
+\end{document}

+ 8 - 8
utils/tply/yaccbase.pas

@@ -33,7 +33,7 @@ $Revision$
 $Modtime: 96-07-31 15:18 $
 
 $History: YACCBASE.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -52,11 +52,11 @@ const
 
 (* symbolic character constants: *)
 
-bs   = #8;      (* backspace character *)
-tab  = #9;      (* tab character *)
-nl   = #10;     (* newline character *)
-cr   = #13;     (* carriage return *)
-ff   = #12;     (* form feed character *)
+bs   = #8;	(* backspace character *)
+tab  = #9;	(* tab character *)
+nl   = #10;	(* newline character *)
+cr   = #13;	(* carriage return *)
+ff   = #12;	(* form feed character *)
 
 var
 
@@ -66,9 +66,9 @@ yfilename     : String;
 pasfilename   : String;
 lstfilename   : String;
 codfilename   : String;
-codfilepath   : String; { Under Linux,
+codfilepath   : String; { Under Linux, 
                           binary and conf file are never in 1 directory.}
-
+                          
 (* Yacc input, output, list and code template file: *)
 
 yyin, yyout, yylst, yycod : Text;

+ 1 - 1
utils/tply/yaccclos.pas

@@ -25,7 +25,7 @@ $Revision$
 $Modtime: 96-07-31 14:09 $
 
 $History: YACCCLOS.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply

+ 12 - 7
utils/tply/yacclook.pas

@@ -26,7 +26,7 @@ $Revision$
 $Modtime: 96-07-31 14:09 $
 
 $History: YACCLOOK.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -156,7 +156,7 @@ uses YaccBase, YaccTabl;
       modified during the previous pass. *)
 
 (* Data structures used in lookahead computation: *)
-
+ 
 type
 
 SymSetArray = array [1..max_set_items] of IntSet;
@@ -267,12 +267,16 @@ procedure spontaneous_lookaheads;
       end;
   end(*spontaneous_lookaheads*);
 
-function redns_less ( i, j : Integer ) : Boolean;{$ifndef fpc}far;{$endif}
-begin
+{$ifndef fpc}{$F+}{$endif}
+function redns_less ( i, j : Integer ) : Boolean;
+{$ifndef fpc}{$F-}{$endif}
+  begin
     redns_less := redn_table^[i].rule_no<redn_table^[j].rule_no
-end(*redns_less*);
+  end(*redns_less*);
 
-procedure redns_swap ( i, j : Integer );{$ifndef fpc}far;{$endif}
+{$ifndef fpc}{$F+}{$endif}
+procedure redns_swap ( i, j : Integer );
+{$ifndef fpc}{$F-}{$endif}
   var x : RednRec;
   begin
     x := redn_table^[i];
@@ -284,7 +288,8 @@ procedure sort_redns;
   (* sort reduction entries in act_state w.r.t. rule numbers *)
   begin
     with state_table^[act_state] do
-      quicksort(redns_lo, redns_hi, {$ifdef fpc}@{$endif}redns_less, {$ifdef fpc}@{$endif}redns_swap);
+      quicksort(redns_lo, redns_hi, {$ifdef fpc}@{$endif}redns_less,
+		{$ifdef fpc}@{$endif}redns_swap);
   end(*sort_redns*);
 
 procedure initialize;

+ 1 - 1
utils/tply/yacclr0.pas

@@ -26,7 +26,7 @@ $Revision$
 $Modtime: 96-07-31 14:09 $
 
 $History: YACCLR0.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply

+ 20 - 20
utils/tply/yaccmsgs.pas

@@ -27,7 +27,7 @@ $Revision$
 $Modtime: 96-07-31 14:50 $
 
 $History: YACCMSGS.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -56,7 +56,7 @@ const
 
 (* sign-on and usage message: *)
 
-sign_on = 'TP Yacc Version 4.1 [May 1998], Copyright (c) 1990-98 Albert Graef';
+sign_on = 'TP Yacc Version 4.1a [April 2000], Copyright (c) 1990-2000 Albert Graef';
 {$ifdef linux}
 usage   = 'Usage: pyacc [options] yacc-file[.y] [output-file[.pas]]';
 {$else}
@@ -79,7 +79,7 @@ rangle_expected                 = '105: > expected';
 ident_expected                  = '106: identifier expected';
 error_in_def                    = '110: error in definition';
 error_in_rule                   = '111: error in rule';
-syntax_error                    = '112: syntax error';
+syntax_error 			= '112: syntax error';
 unexpected_eof                  = '113: unexpected end of file';
 
 (* semantic errors: *)
@@ -90,24 +90,24 @@ double_tokennum_def             = '203: literal already defined';
 unknown_identifier              = '204: unknown identifier';
 type_error                      = '205: type error';
 range_error                     = '206: range error';
-empty_grammar                   = '207: empty grammar?';
+empty_grammar 			= '207: empty grammar?';
 
 (* fatal errors: *)
 
-cannot_open_file                = 'FATAL: cannot open file ';
+cannot_open_file 		= 'FATAL: cannot open file ';
 write_error                     = 'FATAL: write error';
-mem_overflow                    = 'FATAL: memory overflow';
-intset_overflow                 = 'FATAL: integer set overflow';
-sym_table_overflow              = 'FATAL: symbol table overflow';
-nt_table_overflow               = 'FATAL: nonterminal table overflow';
-lit_table_overflow              = 'FATAL: literal table overflow';
-type_table_overflow             = 'FATAL: type table overflow';
-prec_table_overflow             = 'FATAL: precedence table overflow';
-rule_table_overflow             = 'FATAL: rule table overflow';
-state_table_overflow            = 'FATAL: state table overflow';
-item_table_overflow             = 'FATAL: item table overflow';
-trans_table_overflow            = 'FATAL: transition table overflow';
-redn_table_overflow             = 'FATAL: reduction table overflow';
+mem_overflow 			= 'FATAL: memory overflow';
+intset_overflow 		= 'FATAL: integer set overflow';
+sym_table_overflow 		= 'FATAL: symbol table overflow';
+nt_table_overflow 		= 'FATAL: nonterminal table overflow';
+lit_table_overflow 		= 'FATAL: literal table overflow';
+type_table_overflow 		= 'FATAL: type table overflow';
+prec_table_overflow 		= 'FATAL: precedence table overflow';
+rule_table_overflow 		= 'FATAL: rule table overflow';
+state_table_overflow 		= 'FATAL: state table overflow';
+item_table_overflow 		= 'FATAL: item table overflow';
+trans_table_overflow 		= 'FATAL: transition table overflow';
+redn_table_overflow 		= 'FATAL: reduction table overflow';
 
 implementation
 
@@ -166,15 +166,15 @@ procedure fatal(msg : String);
   end(*fatal*);
 
 {$ifndef fpc}
-{$ifndef win32}
-function heapErrorHandler ( size : Word ) : Integer; {$ifndef fpc}far;{$endif}
+{$IFNDEF Win32}
+function heapErrorHandler ( size : Word ) : Integer; far;
   begin
     if size>0 then
       fatal(mem_overflow) (* never returns *)
     else
       heapErrorHandler := 1
   end(*heapErrorHandler*);
-{$endif}
+{$ENDIF}
 {$endif}
 
 begin

+ 2 - 2
utils/tply/yaccpars.pas

@@ -24,7 +24,7 @@ $Revision$
 $Modtime: 96-07-31 14:09 $
 
 $History: YACCPARS.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -237,7 +237,7 @@ procedure build;
                     exclude(symset^, sym);
                   end;
 
-        for i := redns_lo to redns_hi do
+        for i := redns_lo to redns_hi do 
           for j := i+1 to redns_hi do with redn_table^[j] do
             begin
               for k := 1 to size(symset^) do

+ 1 - 1
utils/tply/yaccsem.pas

@@ -24,7 +24,7 @@ $Revision$
 $Modtime: 96-08-01 6:03 $
 
 $History: YACCSEM.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply

+ 33 - 13
utils/tply/yacctabl.pas

@@ -31,7 +31,7 @@ $Revision$
 $Modtime: 96-07-31 21:15 $
 
 $History: YACCTABL.PAS $
- *
+ * 
  * *****************  Version 2  *****************
  * User: Berend       Date: 96-10-10   Time: 21:16
  * Updated in $/Lex and Yacc/tply
@@ -465,7 +465,9 @@ procedure add_lit ( sym : Integer );
     sym_prec^[sym] := 0;
   end(*add_lit*);
 
-function lookup(k : Integer) : String;{$ifndef fpc}far;{$endif}
+{$ifndef fpc}{$F+}{$endif}
+function lookup(k : Integer) : String;
+{$ifndef fpc}{$F-}{$endif}
   (* print name of symbol no. k *)
   begin
     with sym_table^[k] do
@@ -475,7 +477,9 @@ function lookup(k : Integer) : String;{$ifndef fpc}far;{$endif}
         lookup := pname^
   end(*lookup*);
 
-procedure entry(k : Integer; symbol : String);{$ifndef fpc}far;{$endif}
+{$ifndef fpc}{$F+}{$endif}
+procedure entry(k : Integer; symbol : String);
+{$ifndef fpc}{$F-}{$endif}
   (* enter symbol into table *)
   begin
     sym_table^[k].pname := newStr(symbol);
@@ -483,7 +487,8 @@ procedure entry(k : Integer; symbol : String);{$ifndef fpc}far;{$endif}
 
 function get_key ( symbol : String ) : Integer;
   begin
-    get_key := key(symbol, max_keys,{$ifdef fpc}@{$endif}lookup, {$ifdef fpc}@{$endif}entry);
+    get_key := key(symbol, max_keys, {$ifdef fpc}@{$endif}lookup,
+		   {$ifdef fpc}@{$endif}entry);
   end(*get_key*);
 
 procedure def_key ( k : Integer; sym : Integer );
@@ -543,7 +548,9 @@ procedure add_rule ( r : RuleRecPtr );
     rule_table^[n_rules] := r;
   end(*add_rule*);
 
-function rule_less ( i, j : Integer ) : Boolean;{$ifndef fpc}far;{$endif}
+{$ifndef fpc}{$F+}{$endif}
+function rule_less ( i, j : Integer ) : Boolean;
+{$ifndef fpc}{$F-}{$endif}
   begin
     if rule_table^[rule_no^[i]]^.lhs_sym =
        rule_table^[rule_no^[j]]^.lhs_sym then
@@ -553,7 +560,9 @@ function rule_less ( i, j : Integer ) : Boolean;{$ifndef fpc}far;{$endif}
                    rule_table^[rule_no^[j]]^.lhs_sym
   end(*rule_less*);
 
-procedure rule_swap ( i, j : Integer );{$ifndef fpc}far;{$endif}
+{$ifndef fpc}{$F+}{$endif}
+procedure rule_swap ( i, j : Integer );
+{$ifndef fpc}{$F-}{$endif}
   var x : Integer;
   begin
     x := rule_no^[i]; rule_no^[i] := rule_no^[j]; rule_no^[j] := x;
@@ -563,7 +572,8 @@ procedure sort_rules;
   var i : Integer;
   begin
     for i := 1 to n_rules do rule_no^[i] := i;
-    quicksort ( 1, n_rules, {$ifdef fpc}@{$endif}rule_less, {$ifdef fpc}@{$endif}rule_swap );
+    quicksort ( 1, n_rules, {$ifdef fpc}@{$endif}rule_less,
+	       {$ifdef fpc}@{$endif}rule_swap );
   end(*sort_rules*);
 
 procedure rule_offsets;
@@ -603,13 +613,17 @@ procedure add_type ( k : Integer );
 
 (* Routines to sort type identifiers alphabetically: *)
 
-function type_less ( i, j : Integer ) : Boolean;{$ifndef fpc}far;{$endif}
+{$ifndef fpc}{$F+}{$endif}
+function type_less ( i, j : Integer ) : Boolean;
+{$ifndef fpc}{$F-}{$endif}
   begin
     type_less := sym_table^[type_table^[i]].pname^<
                  sym_table^[type_table^[j]].pname^
   end(*type_less*);
 
-procedure type_swap ( i, j : Integer );{$ifndef fpc}far;{$endif}
+{$ifndef fpc}{$F+}{$endif}
+procedure type_swap ( i, j : Integer );
+{$ifndef fpc}{$F-}{$endif}
   var x : Integer;
   begin
     x := type_table^[i];
@@ -621,7 +635,8 @@ procedure sort_types;
   var i, j, count : Integer;
   begin
     (* sort: *)
-    quicksort(1, n_types, {$ifdef fpc}@{$endif}type_less, {$ifdef fpc}@{$endif}type_swap);
+    quicksort(1, n_types, {$ifdef fpc}@{$endif}type_less,
+	      {$ifdef fpc}@{$endif}type_swap);
     (* eliminate dups: *)
     i := 1; j := 1; count := 0;
     while i<=n_types do
@@ -876,7 +891,9 @@ var sort_items : ItemSet;
 
 (* comparison and swap routines for sort_item_set: *)
 
-function items_less ( i, j : Integer ) : Boolean;{$ifndef fpc}far;{$endif}
+{$ifndef fpc}{$F+}{$endif}
+function items_less ( i, j : Integer ) : Boolean;
+{$ifndef fpc}{$F-}{$endif}
   begin
     with sort_items do
       if item[i].pos_no=item[j].pos_no then
@@ -885,7 +902,9 @@ function items_less ( i, j : Integer ) : Boolean;{$ifndef fpc}far;{$endif}
         items_less := item[i].pos_no>item[j].pos_no
   end(*items_less*);
 
-procedure items_swap ( i, j : Integer );{$ifndef fpc}far;{$endif}
+{$ifndef fpc}{$F+}{$endif}
+procedure items_swap ( i, j : Integer );
+{$ifndef fpc}{$F-}{$endif}
   var x : ItemRec;
   begin
     with sort_items do
@@ -897,7 +916,8 @@ procedure items_swap ( i, j : Integer );{$ifndef fpc}far;{$endif}
 procedure sort_item_set ( var item_set : ItemSet );
   begin
     sort_items := item_set;
-    quicksort(1, sort_items.n_items, {$ifdef fpc}@{$endif}items_less, {$ifdef fpc}@{$endif}items_swap);
+    quicksort(1, sort_items.n_items, {$ifdef fpc}@{$endif}items_less,
+	      {$ifdef fpc}@{$endif}items_swap);
     item_set := sort_items;
   end(*sort_item_set*);