[comp.os.minix] Another yacc suitable for porting to Minix

U5569462@ucsvc.unimelb.edu.au (DAVID CLUNIE) (07/19/89)

This is a version of yacc that is NOT derived from the widely
distributed, but allegedly copied from AT&T Unix, version of
yacc. It is slow & ugly but was originally written to run
under CPM on a 64k Z80 system. It duplicates almost all of
yacc's features - all of those that I use anyway. It has been
most recently tested under Zortech C on MSDOS. I have not yet
ported it to Minix or Unix as I currently have neither, but I
see no reason why this could not be achieved with minimal effort.

I post it here so that an enterprising Minix user can do the port
and post the necessary diff's. It has never been my intention
to disseminate this program widely, as there are lots of yacc's
around for various systems that are undoubtedly faster and better.
I do so now due to Minix's special considerations - ie. tiny
segments.

Undoubtedly regular yacc users will find bugs and inconsistencies
in areas of the program that I don't use. I would be most grateful
if they would inform me of these, and I will endeavour to rectify
them ASAP. I use this program a lot, so you may expect enhancements
in the future, especially when I get serious about tuning the
front end of my C compiler for maximum throughput.

If you have never used yacc, try it. You will be amazed at how
easy it is to get a versatile and high quality front end for even
the simplest application when you use yacc to parse the input.
Adding advanced expression handling (regular or arthimetic) is a
piece of cake - when you have done it once, you have done it for
all future applications - just include that bit of the grammar.

I hope this is of use to someone ....

Regards ... David

---- cut here ----
#! /bin/sh
# This is a shell archive.  Remove anything before this line, then unpack
# it by saving it into a file and typing "sh file".
# You can also feed this as standard input via
# unshar, or by typing "sh <file", e.g..
# If this archive is complete, you will see the following message:
#		"End of archive."
#
# Contents:
#
#    csyntax.y
#    cwang.y
#    niceerr.bat
#    testerr.y
#    testerr2.y
#    ya1.c
#    ya2.c
#    yaaug.c
#    yabit.c
#    yacc.c
#    yacc005.doc
#    yaconf.c
#    yacpm.h
#    yadefs.h
#    yafdef.c
#    yafirst.c
#    yafrin.c
#    yafrprec.c
#    yafrreln.c
#    yafrtx.c
#    yafrule.c
#    yafunc.c
#    yagoto.c
#    yaincon.c
#    yainit1.c
#    yalex.c
#    yalex.h
#    yalook.c
#    yalr0.c
#    yaophead.c
#    yaoppars.c
#    yaopsym.c
#    yapack.c
#    yaparse.c
#    yaparse.sed
#    yaparse.y
#    yapcdos.h
#    yardprec.c
#    yardtx.c
#    yaread.c
#    yareln.c
#    yasort.c
#    yasym.c
#    yasystem.h
#    yatable.c
#    yatxsort.c
#    yautil.c
#    yavaxvms.h
#    yavers.h
#    yyerror.c
#    yymain.c
#    yyterror.c
#    yyunion.c
#
if test -f 'csyntax.y' ; then
  echo shar: Will not clobber existing file \"'csyntax.y'\"
else
echo shar: Extracting \"'csyntax.y'\" \( 6167 characters \)
sed "s/^X//" >'csyntax.y' <<'END_OF_FILE'
X%start program
X
X%token TYPEDEF_NAME
X%token GOTO
X%token RETURN
X%token CONTINUE
X%token BREAK
X%token CASE
X%token IF
X%token SEMICOLON
X%token LBRACE
X%token STRUCT
X%token DOUBLE
X%token FLOAT
X%token UNSIGNED
X%token LONG
X%token INT
X%token SHORT
X%token CHAR
X%token REGISTER
X%token EXTERN
X%token RBRACE
X%token STATIC
X%token AUTO
X%token CONSTANT
X%token UNION
X%token IDENTIFIER
X%token STRING
X%token WHILE
X%token FOR
X%token DEFAULT
X%token DO
X%token SWITCH
X%token TYPEDEF
X
X
X%left COMMA
X%right EQUAL ASGNOP
X%right QUESTION COLON
X%left LOR
X%left LAND
X%left BAR
X%left UPARROW
X%left AMPERSAND
X%left LEQUAL LNE
X%left LT GT LE GE
X%left SHR SHL
X%left PLUS MINUS
X%left ASTERISK SLASH PERCENT
X
X%right UASTERISK UAMPERSAND UMINUS EXCLAIM TILDE INCR DECR
X	       SIZEOF 
X
X%left LPAREN RPAREN LBRK RBRK DOT RARROW
X
X%nonassoc ELSE					/* resolve dangling else */
X%nonassoc THEN
X
X%%
X
Xconstant_expression : expression;
X
Xnull_expression : expression			/* use in FOR statements */
X		|
X		;
X
Xexpression : primary
X	   | ASTERISK expression %prec UASTERISK
X	   | AMPERSAND expression %prec UAMPERSAND
X	   | MINUS expression %prec UMINUS
X	   | EXCLAIM expression
X	   | TILDE expression
X	   | INCR primary			/* instead of LVALUE */
X	   | DECR primary
X	   | primary INCR
X	   | primary DECR
X	   | SIZEOF expression
X	   | LPAREN type_name RPAREN expression
X	   | expression QUESTION expression COLON expression
X	   | primary ASGNOP expression		/* instead of LVALUE */
X	   | primary EQUAL expression		/* instead of LVALUE */
X	   | expression COMMA expression
X	   | expression ASTERISK expression
X	   | expression SLASH expression
X	   | expression PERCENT expression
X	   | expression PLUS expression
X	   | expression MINUS expression
X	   | expression SHR expression
X	   | expression SHL expression
X	   | expression LT expression
X	   | expression GT expression
X	   | expression LE expression
X	   | expression GE expression
X	   | expression LEQUAL expression
X	   | expression LNE expression
X	   | expression AMPERSAND expression
X	   | expression UPARROW expression
X	   | expression BAR expression
X	   | expression LAND expression
X	   | expression LOR expression
X	   ;
X
Xprimary : IDENTIFIER				/* use wherever LVALUE */
X	| CONSTANT
X	| STRING
X	| LPAREN expression RPAREN
X	| primary LPAREN RPAREN
X	| primary LPAREN expression RPAREN
X	| primary LBRK expression RBRK
X	| primary RARROW IDENTIFIER
X	| primary DOT IDENTIFIER
X	;
X
Xdeclaration : decl_specifiers
X	    | decl_specifiers init_declarator_list
X	    ;
X
Xdecl_specifiers : type_specifier decl_specifiers
X		| sc_specifier decl_specifiers
X		|
X		;
X
Xsc_specifier : AUTO
X	     | STATIC
X	     | EXTERN
X	     | REGISTER
X	     | TYPEDEF
X	     ;
X
Xtype_specifier  : CHAR
X		| SHORT
X		| INT
X		| LONG
X		| UNSIGNED
X		| FLOAT
X		| DOUBLE
X		| struct_or_union_specifier
X		| TYPEDEF_NAME
X		|
X		;
X
Xinit_declarator_list : init_declarator
X		     | init_declarator COMMA init_declarator_list
X		     |
X		     ;
X
Xinit_declarator : declarator initializer
X		;
X
Xdeclarator : IDENTIFIER
X	   | LPAREN declarator RPAREN
X	   | ASTERISK declarator
X	   | declarator LPAREN RPAREN
X	   | declarator LBRK RBRK
X	   | declarator LBRK constant_expression RBRK
X	   ;
X
Xstruct_or_union_specifier : STRUCT LBRACE struct_decl_list RBRACE
X			  | STRUCT IDENTIFIER LBRACE struct_decl_list RBRACE
X			  | STRUCT IDENTIFIER
X			  | UNION LBRACE struct_decl_list RBRACE
X			  | UNION IDENTIFIER LBRACE struct_decl_list RBRACE
X			  | UNION IDENTIFIER
X			  ;
X
Xstruct_decl_list : struct_declaration
X		 | struct_declaration struct_decl_list
X		 ;
X
Xstruct_declaration : type_specifier struct_declarator_list
X		   ;
X
Xstruct_declarator_list : struct_declarator
X		       | struct_declarator COMMA struct_declarator_list
X		       ;
X
Xstruct_declarator : declarator
X		  | declarator COLON constant_expression
X		  | COLON constant_expression
X		  ;
X
Xinitializer : EQUAL expression
X	    | EQUAL LBRACE initializer_list RBRACE
X	    | EQUAL LBRACE initializer_list COMMA RBRACE
X	    |
X	    ;
X
Xinitializer_list : expression
X		 | initializer_list COMMA initializer_list
X		 | LBRACE initializer_list RBRACE
X		 ;
X
Xtype_name : type_specifier
X	  | type_specifier abstract_declarator
X	  ;
X
Xabstract_declarator : LPAREN abstract_declarator RPAREN
X		    | ASTERISK abstract_declarator
X		    | abstract_declarator LPAREN RPAREN
X		    | abstract_declarator LBRK RBRK
X		    | abstract_declarator LBRK constant_expression RBRK
X		    |
X		    ;
X
Xcompound_statement : LBRACE declaration_list RBRACE
X		   | LBRACE declaration_list statement_list RBRACE
X		   | LBRACE statement_list RBRACE
X		   | LBRACE RBRACE
X		   ;
X
Xdeclaration_list : declaration
X		 | declaration declaration_list
X		 |
X		 ;
X
Xstatement_list : statement
X	       | statement statement_list
X	       |
X	       ;
X
Xstatement : compound_statement
X	  | expression SEMICOLON
X	  | IF LPAREN expression RPAREN statement %prec THEN
X	  | IF LPAREN expression RPAREN statement ELSE statement
X	  | WHILE LPAREN expression RPAREN statement
X	  | DO statement WHILE LPAREN expression RPAREN SEMICOLON
X
X	  | FOR LPAREN null_expression SEMICOLON null_expression
X		SEMICOLON null_expression RPAREN statement
X
X	  | SWITCH LPAREN expression RPAREN statement
X	  | CASE constant_expression COLON statement
X	  | DEFAULT COLON statement
X	  | BREAK SEMICOLON
X	  | CONTINUE SEMICOLON
X	  | RETURN expression SEMICOLON
X	  | GOTO IDENTIFIER SEMICOLON
X	  | IDENTIFIER COLON statement		/* IDENTIFIER -> S/R dt. ?: */
X	  | SEMICOLON
X	  ;
X
Xprogram : external_definition
X	| external_definition program
X	;
X
Xexternal_definition : function_definition
X		    | data_definition
X		    ;
X
Xfunction_definition : function_declarator function_body
X		    | type_specifier function_declarator function_body
X		    ;
X
Xfunction_declarator : declarator LPAREN RPAREN
X		    | declarator LPAREN parameter_list RPAREN
X		    ;
X
Xparameter_list : IDENTIFIER
X	       | IDENTIFIER COMMA parameter_list
X	       |
X	       ;
X
Xfunction_body : type_decl_list function_statement
X	      ;
X
Xtype_decl_list : declaration_list
X	       ;
X
Xfunction_statement : LBRACE declaration_list statement_list RBRACE
X		   ;
X
Xdata_definition : data_specifier type_specifier init_declarator_list
X		;
X
Xdata_specifier : EXTERN
X	       | STATIC
X	       |
X      	       ;
END_OF_FILE
if test 6167 -ne `wc -c <'csyntax.y'`; then
    echo shar: \"'csyntax.y'\" unpacked with wrong size!
fi
# end of 'csyntax.y'
fi
if test -f 'cwang.y' ; then
  echo shar: Will not clobber existing file \"'cwang.y'\"
else
echo shar: Extracting \"'cwang.y'\" \( 7166 characters \)
sed "s/^X//" >'cwang.y' <<'END_OF_FILE'
X%token IDENTIFIER CONSTANT STRING_LITERAL SIZEOF
X%token PTR_OP INC_OP DEC_OP LEFT_OP RIGHT_OP LE_OP GE_OP EQ_OP NE_OP
X%token AND_OP OR_OP MUL_ASSIGN DIV_ASSIGN MOD_ASSIGN ADD_ASSIGN
X%token SUB_ASSIGN LEFT_ASSIGN RIGHT_ASSIGN AND_ASSIGN
X%token XOR_ASSIGN OR_ASSIGN TYPEDEF_NAME ENUM_CONST
X
X%token TYPEDEF EXTERN STATIC AUTO REGISTER
X%token CHAR SHORT INT LONG SIGNED UNSIGNED FLOAT DOUBLE CONST VOLATILE VOID
X%token STRUCT UNION ENUM ELLIPSIS
X
X%token CASE DEFAULT IF ELSE SWITCH WHILE DO FOR GOTO CONTINUE BREAK RETURN
X
X%start file
X%%
X
Xprimary_expr
X	: identifier
X	| CONSTANT
X	| STRING_LITERAL
X	| '(' expr ')'
X	;
X
Xpostfix_expr
X	: primary_expr
X	| postfix_expr '[' expr ']'
X	| postfix_expr '(' ')'
X	| postfix_expr '(' argument_expr_list ')'
X	| postfix_expr '.' identifier
X	| postfix_expr PTR_OP identifier
X	| postfix_expr INC_OP identifier
X	| postfix_expr DEC_OP identifier
X	;
X
Xargument_expr_list
X	: assignment_expr
X	| argument_expr_list ',' assignment_expr
X	;
X
Xunary_expr
X	: postfix_expr
X	| INC_OP unary_expr
X	| DEC_OP unary_expr
X	| unary_operator cast_expr
X	| SIZEOF unary_expr
X	| SIZEOF '(' type_name ')'
X	;
X
Xunary_operator
X	: '&'
X	| '*'
X	| '+'
X	| '-'
X	| '~'
X	| '!'
X	;
X
Xcast_expr
X	: unary_expr
X	| '(' type_name ')' cast_expr
X	;
X
Xmultiplicative_expr
X	: cast_expr
X	| multiplicative_expr '*' cast_expr
X	| multiplicative_expr '/' cast_expr
X	| multiplicative_expr '%' cast_expr
X	;
X
Xadditive_expr
X	: multiplicative_expr
X	| additive_expr '+' multiplicative_expr
X	| additive_expr '-' multiplicative_expr
X	;
X
Xshift_expr
X	: additive_expr
X	| shift_expr LEFT_OP additive_expr
X	| shift_expr RIGHT_OP additive_expr
X	;
X
Xrelational_expr
X	: shift_expr
X	| relational_expr '<' shift_expr
X	| relational_expr '>' shift_expr
X	| relational_expr LE_OP shift_expr
X	| relational_expr GE_OP shift_expr
X	;
X
Xequality_expr
X	: relational_expr
X	| equality_expr EQ_OP relational_expr
X	| equality_expr NE_OP relational_expr
X	;
X
Xand_expr
X	: equality_expr
X	| and_expr '&' equality_expr
X	;
X
Xexclusive_or_expr
X	: and_expr
X	| exclusive_or_expr '^' and_expr
X	;
X
Xinclusive_or_expr
X	: exclusive_or_expr
X	| inclusive_or_expr '|' exclusive_or_expr
X	;
X
Xlogical_and_expr
X	: inclusive_or_expr
X	| logical_and_expr AND_OP inclusive_or_expr
X	;
X
Xlogical_or_expr
X	: logical_and_expr
X	| logical_or_expr OR_OP logical_and_expr 
X	;
X
Xconditional_expr
X	: logical_or_expr
X	| logical_or_expr '?' expr : conditional_expr
X	;
X
Xassignment_expr
X	: conditional_expr
X	| unary_expr assignment_operator assignment_expr
X	;
X
Xassignment_operator
X	: '='
X	| ADD_ASSIGN
X	| AND_ASSIGN
X	| DIV_ASSIGN
X	| LEFT_ASSIGN
X	| MOD_ASSIGN
X	| MUL_ASSIGN
X	| OR_ASSIGN
X	| RIGHT_ASSIGN
X	| SUB_ASSIGN
X	| XOR_ASSIGN
X	;
X
Xexpr
X	: assignment_expr
X	| expr ',' assignment_expr
X	;
X
Xconstant_expr
X	: conditional_expr
X	;
X
Xdeclaration
X	: declaration_specifiers ';'
X	| declaration_specifiers init_declarator_list ';'
X	;
X
Xdeclaration_specifiers
X	: ssc_specifier
X	| ssc_specifier declaration_specifiers
X	| type_specifier
X	| type_specifier declaration_specifiers
X	;
X
Xinit_declarator_list
X	: init_declarator
X	| init_declarator_list ',' init_declarator
X	;
X
Xinit_declarator
X	: declarator
X	| declarator '=' initializer
X	;
X
Xssc_specifier
X	: AUTO
X	| EXTERN
X	| REGISTER
X	| STATIC
X	| TYPEDEF
X	;
X
Xtype_specifier
X	: CHAR
X	| CONST
X	| DOUBLE
X	| FLOAT
X	| INT
X	| LONG
X	| SHORT
X	| SIGNED
X	| TYPEDEF_NAME
X	| UNSIGNED
X	| VOID
X	| VOLATILE
X	| struct_or_union_specifier
X	| enum_specifier
X	;
X
Xstruct_or_union_specifier
X	: struct_or_union identifier
X	| struct_or_union identifier '{' struct_declaration_list '}'
X	| struct_or_union '{' struct_declaration_list '}'
X	;
X
Xstruct_or_union
X	: STRUCT
X	| UNION
X	;
X
Xstruct_declaration_list
X	: struct_declaration
X	| struct_declaration_list struct_declaration
X	;
X
Xstruct_declaration
X	: type_specifier_list struct_declarator_list ';'
X	;
X
Xtype_specifier_list
X	: type_specifier
X	| type_specifier_list type_specifier
X	;
X
Xstruct_declarator_list
X	: struct_declarator
X	| struct_declarator_list ',' struct_declarator
X	;
X
Xstruct_declarator
X	: declarator
X	| ':' constant_expr
X	| declarator ':' constant_expr
X	;
X
Xenum_specifier
X	: ENUM '{' enumerator_list '}'
X	| ENUM identifier '{' enumerator_list '}'
X	| ENUM identifier
X	;
X
Xenumerator_list
X	: enumerator
X	| enumerator_list ',' enumerator
X	;
X
Xenumerator
X	: ENUM_CONST
X	| ENUM_CONST '=' constant_expr
X	;
X
Xdeclarator
X	: declarator2
X	| pointer declarator2
X	;
X
Xdeclarator2
X	: identifier
X	| '(' declarator ')'
X	| declarator2 '[' ']'
X	| declarator2 '[' constant_expr ']'
X	| declarator2 '(' ')'
X	| declarator2 '(' identifier_list ')'
X	| declarator2 '(' parameter_type_list ')'
X	;
X
Xpointer
X	: '*'
X	| '*' type_specifier_list
X	| '*' pointer
X	| '*' type_specifier_list pointer
X	;
X
Xparameter_type_list
X	: parameter_list
X	| parameter_list ',' ELLIPSIS
X	;
X
Xparameter_list
X	: parameter_declaration
X	| parameter_list ',' parameter_declaration
X	;
X
Xparameter_declaration
X	: declaration_specifiers
X	| declaration_specifiers declarator
X	| declaration_specifiers abstract_declarator
X	;
X
Xidentifier_list
X	: identifier
X	| identifier_list ',' identifier
X	;
X
Xtype_name
X	: type_specifier_list
X	| type_specifier_list abstract_declarator
X	;
X
Xabstract_declarator
X	: pointer
X	| abstract_declarator2
X	| pointer abstract_declarator2
X	;
X
Xabstract_declarator2
X	: '(' abstract_declarator ')'
X	| '[' ']'
X	| '[' constant_expr ']'
X	| abstract_declarator2 '[' ']'
X	| abstract_declarator2 '[' constant_expr ']'
X	| '(' ')'
X	| '(' parameter_type_list ')'
X	| abstract_declarator2 '(' ')'
X	| abstract_declarator2 '(' parameter_type_list ')'
X	;
X
Xinitializer
X	: assignment_expr
X	| '{' initializer_list '}'
X	| '{' initializer_list ',' '}'
X	;
X
X
Xinitializer_list
X	: initializer
X	| initializer_list ',' initializer
X	;
X
Xstatement
X	: labeled_statement
X	| compound_statement
X	| expression_statement
X	| selection_statement
X	| iteration_statement
X	| jump_statement
X	;
X
Xlabeled_statement
X	: identifier ':' statement
X	| CASE constant_expr ':' statement
X	| DEFAULT ':' statement
X	;
X
Xcompound_statement
X	: '{' '}'
X	| '{' statement_list '}'
X	| '{' declaration_list '}'
X	| '{' declaration_list statement_list '}'
X	;
X
Xdeclaration_list
X	: declaration
X	| declaration_list declaration
X	;
X
Xstatement_list
X	: statement
X	| statement_list statement
X	;
X
Xexpression_statement
X	: ';'
X	| expr ';'
X	;
X
Xselection_statement
X	: IF '(' expr ')' statement
X	| IF '(' expr ')' statement ELSE statement
X	| SWITCH '(' expr ')' statement
X	;
X
Xiteration_statement
X	: WHILE '(' expr ')' statement
X	| DO statement WHILE '(' expr ')' ';'
X	| FOR '(' ';' ';' ')' statement
X	| FOR '(' ';' ';' expr ')' statement
X	| FOR '(' ';' expr ';' ')' statement
X	| FOR '(' ';' expr ';' expr ')' statement
X	| FOR '(' expr ';' ';' ')' statement
X	| FOR '(' expr ';' ';' expr ')' statement
X	| FOR '(' expr ';' expr ';' ')' statement
X	| FOR '(' expr ';' expr ';' expr ')' statement
X	;
X
Xjump_statement
X	: GOTO identifier ';'
X	| CONTINUE ';'
X	| BREAK ';'
X	| RETURN ';'
X	| RETURN expr ';'
X	;
X
Xfile
X	: external_definition
X	| file external_definition
X	;
X
Xexternal_definition
X	: function_definition
X	| declaration
X	;
X
Xfunction_definition
X	: declarator function_body
X	| declaration_specifiers declarator function_body
X	;
X
Xfunction_body
X	: compound_statement
X	| declaration_list compound_statement
X	;
X
Xidentifier
X	: IDENTIFIER
X	;
X%%
END_OF_FILE
if test 7166 -ne `wc -c <'cwang.y'`; then
    echo shar: \"'cwang.y'\" unpacked with wrong size!
fi
# end of 'cwang.y'
fi
if test -f 'niceerr.bat' ; then
  echo shar: Will not clobber existing file \"'niceerr.bat'\"
else
echo shar: Extracting \"'niceerr.bat'\" \( 93 characters \)
sed "s/^X//" >'niceerr.bat' <<'END_OF_FILE'
Xdel yaparse.c
Xmake
Xsed -f yaparse.sed <yaparse.c >temp
Xdel yaparse.c
Xren temp yaparse.c
Xmake
END_OF_FILE
if test 93 -ne `wc -c <'niceerr.bat'`; then
    echo shar: \"'niceerr.bat'\" unpacked with wrong size!
fi
# end of 'niceerr.bat'
fi
if test -f 'testerr.y' ; then
  echo shar: Will not clobber existing file \"'testerr.y'\"
else
echo shar: Extracting \"'testerr.y'\" \( 487 characters \)
sed "s/^X//" >'testerr.y' <<'END_OF_FILE'
X%%
Xfile : line nl
X     | file line nl
X     ;
X
Xline : char
X     | line char
X     | line error	{ yyerror("bad char in line"); }
X     | error		{ yyerror("bad char at start of line"); }
X     ;
X
Xchar : 'a' | 'b' | 'c' ;
Xnl   : '\n' ;
X
X%%
X/* Yymain.c 14-Jan-87 */
X
X#include <stdio.h>
X
Xextern int yydebug;
XYYSTYPE yylval;
X
Xmain()
X{
X    yydebug=1;
X    return (yyparse());
X}
X
Xyyerror(s)
Xchar *s;
X{
X    fprintf(stderr,"%s\n",s);
X}
X
Xyylex()
X{
X    int c;
X    return (c=getchar()) == EOF ? 0 : c;
X}
X
END_OF_FILE
if test 487 -ne `wc -c <'testerr.y'`; then
    echo shar: \"'testerr.y'\" unpacked with wrong size!
fi
# end of 'testerr.y'
fi
if test -f 'testerr2.y' ; then
  echo shar: Will not clobber existing file \"'testerr2.y'\"
else
echo shar: Extracting \"'testerr2.y'\" \( 613 characters \)
sed "s/^X//" >'testerr2.y' <<'END_OF_FILE'
X%%
Xfile : linegroup
X     | file linegroup
X     ;
X
Xlinegroup
X     : unstarline nl
X     | starline '*' nl
X     ;
X
Xstarline
X     : line
X     ;
X
Xunstarline
X     : line
X     ;
X
Xline : char
X     | line char
X     | line error	{ yyerror("bad char in line"); }
X     | error		{ yyerror("bad char at start of line"); }
X     ;
X
Xchar : 'a' | 'b' | 'c' ;
Xnl   : '\n' ;
X
X%%
X/* Yymain.c 14-Jan-87 */
X
X#include <stdio.h>
X
Xextern int yydebug;
XYYSTYPE yylval;
X
Xmain()
X{
X    yydebug=1;
X    return (yyparse());
X}
X
Xyyerror(s)
Xchar *s;
X{
X    fprintf(stderr,"%s\n",s);
X}
X
Xyylex()
X{
X    int c;
X    return (c=getchar()) == EOF ? 0 : c;
X}
X
END_OF_FILE
if test 613 -ne `wc -c <'testerr2.y'`; then
    echo shar: \"'testerr2.y'\" unpacked with wrong size!
fi
# end of 'testerr2.y'
fi
if test -f 'ya1.c' ; then
  echo shar: Will not clobber existing file \"'ya1.c'\"
else
echo shar: Extracting \"'ya1.c'\" \( 282 characters \)
sed "s/^X//" >'ya1.c' <<'END_OF_FILE'
X/* Ya1.c */
X/* 22-Jul-87 IBM */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X#include <stdio.h>
X
X#define DEFINE
X#define PHASE1
X
X#include "yadefs.h"
X
END_OF_FILE
if test 282 -ne `wc -c <'ya1.c'`; then
    echo shar: \"'ya1.c'\" unpacked with wrong size!
fi
# end of 'ya1.c'
fi
if test -f 'ya2.c' ; then
  echo shar: Will not clobber existing file \"'ya2.c'\"
else
echo shar: Extracting \"'ya2.c'\" \( 288 characters \)
sed "s/^X//" >'ya2.c' <<'END_OF_FILE'
X/* Ya2.c	20-Oct-86 */
X/* 29-Mar-87 */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X#include <stdio.h>
X
X#define DEFINE
X#define PHASE2
X
X#include "yadefs.h"
X
END_OF_FILE
if test 288 -ne `wc -c <'ya2.c'`; then
    echo shar: \"'ya2.c'\" unpacked with wrong size!
fi
# end of 'ya2.c'
fi
if test -f 'yaaug.c' ; then
  echo shar: Will not clobber existing file \"'yaaug.c'\"
else
echo shar: Extracting \"'yaaug.c'\" \( 863 characters \)
sed "s/^X//" >'yaaug.c' <<'END_OF_FILE'
X/* Yaaug.c	21-Jan-87 	Augment grammar with head symbol */
X/* 22-Jul-87 IBM */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	augment()
X
X	Uses:		addrule()	setnont()	addlist()
X			chksym()
X*/
X
X#include <stdio.h>
X
X#define PHASE1
X
X#include "yadefs.h"
X
Xvoid
Xaugment()
X{
X    RULE *addrule(),*rule;
X    void setnont(),addlist();
X    SYMBOL *chksym();
X
X    /* Augment grammar with	$accept : start $end ; */
X
X    rule=addrule();
X    settok(send=chksym(ENDNAME),ENDTOKEN);
X    addlist(rule,sstart);
X    addlist(rule,send);
X    setnont(sstart=chksym(ACCEPTNAME));
X    sstart->rule=rule;
X    rule->sym=sstart;	/* not filled by addrule() */
X    rule->seq=0;	/* This value not used yet */
X    rule->next=NULL;
X
X    cnrule=nextrule;
X}
X
END_OF_FILE
if test 863 -ne `wc -c <'yaaug.c'`; then
    echo shar: \"'yaaug.c'\" unpacked with wrong size!
fi
# end of 'yaaug.c'
fi
if test -f 'yabit.c' ; then
  echo shar: Will not clobber existing file \"'yabit.c'\"
else
echo shar: Extracting \"'yabit.c'\" \( 2266 characters \)
sed "s/^X//" >'yabit.c' <<'END_OF_FILE'
X/* Yabit.c	30-Oct-86	Bit handling routines */
X/* 25-Jul-87 IBM */
X/* 25-Mar-88 VAXVMS */
X/* 23-Apr-88 */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	eqbit()		orbit()		copybit()
X			zerobit()
X			[#ifndef BITMACRO
X			isbit()		setbit()	clrbit()
X			sizebit()	alcbit()]
X			
X*/
X
X#include <stdio.h>
X
X#include "yadefs.h"
X
Xint
Xeqbit(to,from,n)
XBITSTR *to,*from;
Xint n;
X{
X    int i;
X
X    for (i=0; i<sizebit(n); ++i) {
X	if (*from++ != *to++) {
X	    return 0;
X	}
X    }
X    return 1;
X}
X
X#ifdef AND				/* Not used any more */
Xint
Xandbit(to,from,n)
XBITSTR *to,*from;
Xint n;
X{
X    int i,overlap;
X
X    overlap=0;
X    for (i=0; i<sizebit(n); ++i) {
X	if (*from=(*to & *from)) {
X	    ++overlap;
X	}
X	++to;
X	++from;
X    }
X    return overlap;
X}
X#endif
X
Xint
Xorbit(to,from,n)
XBITSTR *to,*from;
Xint n;
X{
X    int i,added;
X
X	/* NB. For last word, may not all be be in use as bit string */
X	/* but both unused tails will be 0 since zerobit() and hence */
X	/* won't interfere with the comparison or the or operation */
X
X    added=0;
X    for (i=0; i<sizebit(n); ++i) {
X	trace(("*to=%04x *from=%04x &=%04x ^=%04x\n",
X		*to,*from,(*to & *from),(*from ^ (*to & *from))));
X	if (*from ^ (*to & *from)) {	/* If there is anything in from that */
X					/* is not already in to */
X	    *to|= *from;		/* Add it to to */
X					/* "= *" avoids old assignment op */
X	    trace(("new *to=%04x\n",*to));
X	    ++added;
X	}
X	++to;
X	++from;
X    }
X    return added;
X}
X
Xvoid
Xcopybit(to,from,n)
XBITSTR *to,*from;
Xint n;
X{
X    int i;
X
X    for(i=0; i<sizebit(n); ++i) *to++= *from++;
X					/* "= *" avoids old assignment op */
X}
X
Xvoid
Xzerobit(s,n)
XBITSTR *s;
Xint n;
X{
X    int i;
X
X    for(i=0; i<sizebit(n); ++i) *s++=0;
X}
X
X#ifndef BITMACRO
X
Xint
Xisbit(s,n)
XBITSTR *s;
Xint n;
X{
X    return ( ((s)[(n) / BITLNG]) &  (1 << ((n) % BITLNG)) );
X}
X
Xvoid
Xsetbit(s,n)
XBITSTR *s;
Xint n;
X{
X    ( ((s)[(n) / BITLNG]) |= (1 << ((n) % BITLNG)) );
X}
X
Xvoid
Xclrbit(s,n)
XBITSTR *s;
Xint n;
X{
X    ( ((s)[(n) / BITLNG]) &= ~(1 << ((n) % BITLNG)) );
X}
X
Xint
Xsizebit(n)
Xint n;
X{
X    return ( (n-1)/BITLNG+1 );
X}
X
XBITSTR *
Xalcbit(n)
Xint n;
X{
X    return ( (BITSTR *)xalloc(sizebit(n)*BITBYTE) );
X}
X
X#endif
END_OF_FILE
if test 2266 -ne `wc -c <'yabit.c'`; then
    echo shar: \"'yabit.c'\" unpacked with wrong size!
fi
# end of 'yabit.c'
fi
if test -f 'yacc.c' ; then
  echo shar: Will not clobber existing file \"'yacc.c'\"
else
echo shar: Extracting \"'yacc.c'\" \( 2912 characters \)
sed "s/^X//" >'yacc.c' <<'END_OF_FILE'
X/* Yacc.c	23-Jan-87 */
X/* 25-Jul-87 IBM */
X/* 30-Nov-88 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	main()
X
X	Uses:		augment()	init1()		fini1()
X			yyparse()	rdstr()		rdsym()
X			rdrule()	dump()		mkfirst()
X			frfirst()	lr0()		rdtx()
X			frtx()		mkgoto()	lookahead()
X			rdincon()	frincon()	mkreln()
X			frreln()	txsort()	shsort()
X			rdprec()	frprec()	conf()
X			pack()		oppars()
X*/
X
X#include <stdio.h>
X
X#define DEFINE
X#define PHASE0
X
X#include "yadefs.h"
X
X#ifdef TIMEHEAD
X#include TIMEHEAD
X#endif
X
Xmain(argc,argv)
Xint argc;
Xchar *argv[];
X{
X    void augment(),init1(),fini1();
X    int yyparse();
X    void rdstr(),rdsym(),rdrule();
X#ifdef TRACE
X    dumpglbl();
X#endif
X    void mkfirst(),frfirst();
X    void lr0();
X    void rdtx(),frtx(),mkgoto();
X    void lookahead();
X    void rdincon(),frincon();
X    void mkreln(),frreln();
X    void txsort(),shsort();
X    void rdprec(),frprec(),conf(),pack();
X    void oppars();
X    clock_t t,f;
X
X    init1(argc,argv);		/* Phase 1 */
X    if (o_debug) {
X	t=clock();
X    }
X    if (yyparse() || cnfatal) {
X	exit(1);
X    }
X    augment();
X    fini1();
X    if (cnfatal) exit(1);
X#ifdef TRACE
X    dumpglbl();
X#endif
X    rdstr();			/* Phase 2 */
X#ifdef TRACE
X    dumpglbl();
X#endif
X    unlink(nstring);
X#ifdef TRACE
X    dumpglbl();
X#endif
X    rdsym();
X#ifdef TRACE
X    dumpglbl();
X#endif
X    rdrule();
X#ifdef TRACE
X    dumpglbl();
X#endif
X    unlink(nrhs);
X#ifdef TRACE
X    dumpglbl();
X#endif
X    mkfirst();
X#ifdef TRACE
X    dumpglbl();
X#endif
X    lr0();
X#ifdef TRACE
X    dumpglbl();
X#endif
X    frfirst();
X    txsort();
X    rdtx();
X    rdincon();
X    mkreln();
X    unlink(ntr2);
X    lookahead();
X    frreln();
X    mkgoto();
X    frtx();
X    rdprec();
X    unlink(nsymbol);
X    unlink(nrule);
X    conf();
X    unlink(ntrans);
X    unlink(nitem);
X    frprec();
X    frincon();
X    pack();
X    unlink(nshift);
X    unlink(ngoto);
X    oppars();			/* Phase 3 */
X    unlink(naction);
X    if (o_debug) {
X	f=100/CLK_TCK;	/* make sure we have 1/100ths of a second */
X	t=(clock()-t)*f;
X	printf("Elapsed time %lu.%02lu seconds \n",
X	    (long)(t/100),(long)(t%100));
X    }
X    exit(0);
X}
X
X#ifdef TRACE
X
Xvoid
Xdumpglbl()
X{
Xprintf("cnwarning\t%d\n",cnwarning);
Xprintf("cnfatal\t%d\n",cnfatal);
Xprintf("cnstr\t%d\n",cnstr);
Xprintf("cnrule\t%d\n",cnrule);
Xprintf("cnrhs\t%d\n",cnrhs);
Xprintf("cnnont\t%d\n",cnnont);
Xprintf("cntok\t%d\n",cntok);
Xprintf("bstok\t%d\n",bstok);
Xprintf("bsnont\t%d\n",bsnont);
Xprintf("start\t%d\n",start);
Xprintf("cnstate\t%d\n",cnstate);
Xprintf("cnitem\t%d\n",cnitem);
Xprintf("cnincon\t%d\n",cnincon);
Xprintf("cncxst\t%d\n",cncxst);
Xprintf("cncxit\t%d\n",cncxit);
Xprintf("cnntx\t%d\n",cnntx);
Xprintf("cnttx\t%d\n",cnttx);
Xprintf("cnrtx\t%d\n",cnrtx);
Xprintf("cnshift\t%d\n",cnshift);
Xprintf("cngo\t%d\n",cngo);
X}
X
X#endif /* TRACE */
X
END_OF_FILE
if test 2912 -ne `wc -c <'yacc.c'`; then
    echo shar: \"'yacc.c'\" unpacked with wrong size!
fi
# end of 'yacc.c'
fi
if test -f 'yacc005.doc' ; then
  echo shar: Will not clobber existing file \"'yacc005.doc'\"
else
echo shar: Extracting \"'yacc005.doc'\" \( 4697 characters \)
sed "s/^X//" >'yacc005.doc' <<'END_OF_FILE'
X09-Jul-89  Yacc version 0.05 Release Notes
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
XThis is a preliminary version of yacc.
X
XThis is not a rehash of DECUS yacc, nor is it the yacc available from the
XC User's Group or the Austin Codeworks.
X
XIe. it is "yet another" yacc !
X
XAlthough the yacc program itself is completely new, it uses a modified
Xversion of the DECUS yacc driver program "yaccpar". This in turn is
Xbased on an old Unix version. Some features of the System V driver, have
Xbeen included. The table formats are almost, but not completely identical.
X
XI haven't written any documentation yet, but the program behaves pretty much
Xlike Unix yacc, and accepts all the current syntax. The program describes
Xitself when invoked with the -h option.
X
XI offer no apologies for the appallingly slow implementation of DeRemer's
Xalgorithm, with the use of multiple disk based temporary files. The code
Xis organized this way so that the absolute minimum amount of memory is
Xin use at any time, and the routines are capable of being overlayed. This
Xis all because the original program ran on an old CPM 64K Z80 machine with
Xabout 20K of free memory available. It managed to handle a complete grammar
Xfor a draft ANSI standard C compiler, so don't knock it !
X
XOne day I might change it around to use memory properly and run at a more
Xreasonable pace, but don't hold your breath.
X
XOther things I may do include exhaustively testing GNU bison and making my
Xyacc as compatible with theirs as possible. I really must clean up my tables
Xand make them absolutely Sys V compatible, especially when it comes to some
Xof their optimizations. I have never really tried to speed up the skeleton
Xparser, and I am sure it could be made to run much faster. One day I may
Xeven write a utility to covert the output tables, or the youtput file, to
Xinline assembly code using branch tables rather than interpreted tables a la
XDeRemer's other article. The error handling would be a hassle though.
X
XI have not exhaustively tested some of the more subtle yacc features, though
XI think I have probably used most of them in my day to day work. I have not
Xcome across a serious bug in at least a year. However, I dare say that anyone
Xelse who uses it will probably come across a few, so please let me know and
XI will fix them ASAP. Same goes for ports to other machines, let me have your
Xefforts and I will incorporate them into the distribution. Who knows, one
Xday I might release version 1.00 !
X
XFeatures.
X
XSkeleton includes the ability to list the expected lookahead symbols in the
Xevent of a syntax error. Turn on YYFULLERR to get this and link with
Xyyterror() which is called repeatedly for each lookahead symbol, rather than
Xa single call to yyerror(). This idea was derived from Axel T. Schriener's
Xbook & modified to use SysV-like tables.
X
XNote that the parser used by yacc itself uses the YYFULLERR mechanism. It is
Xturned on in the distributed version. If you don't want it on, just define
XYYFULLERR 0 in the top of yaparse.y.
X
XIf you want fancy descriptions of each symbol, rather than just the token
Xname automatically generated by yacc, you can edit the c file output by
Xyacc. See the files niceerr.bat and yaparse.sed to see how this is done.
X
XCompiling the sources.
X
XThe supplied makefile is for Zortech C version 1.06 under MSDOS.
X
XTo get fancy syntax error messages, run the file niceerr.bat instead of
Xjust saying make. Note that you need sed to do this. I use the version
Xfrom Mortice Kern's toolkit. I don't do the sed within the makefile because
Xsomething goes wrong with i/o redirection using Zortech make and MKS tools.
X
XLimitations and Bugs.
X
XThe older syntax variations (eg. ={ instead of {, etc.) are not yet supported.
X
XSyntax errors bomb out straight away, semantic errors keep trying (needless to
Xsay the yacc parser is written in yacc).
X
XLimited type checking of the value stack is provided. Anything legal is
Xaccepted, but there are some subtle illegal cases which are not yet detected,
Xfor example, explicitly declaring an embedded action return value with one type
Xand later in the rule referring to it with another type. This will be improved
Xin a later release.
X
XIf you abort the program, the disk will be littered with temporary files with
Xthe extension .$$$ which can be deleted.
X
XTemporary file names, as well as output file names are fixed, so don't try
Xrunning two yacc processes simultaneously.
X
XThe VAX VMS and CPM implementations have not been tested in a long time, so
Xsome minor mods that have been made since may prevent uneventful compilation !
END_OF_FILE
if test 4697 -ne `wc -c <'yacc005.doc'`; then
    echo shar: \"'yacc005.doc'\" unpacked with wrong size!
fi
# end of 'yacc005.doc'
fi
if test -f 'yaconf.c' ; then
  echo shar: Will not clobber existing file \"'yaconf.c'\"
else
echo shar: Extracting \"'yaconf.c'\" \( 11155 characters \)
sed "s/^X//" >'yaconf.c' <<'END_OF_FILE'
X/* Yaconf.c	27-Nov-86	Scan transitions resolving conflicts */
X/* 05-Jan-87	NB. All external (youtput,yxdef[],yxexca[]) references to */
X/*		rules are to the ruleseq[] number, NOT to the internally */
X/*		used rule number in fitem, etc - this is in order to use */
X/*		the sequence number to index the action case statement */
X/*		The internal number is different, since rules are grouped by */
X/*		parent nonterminal */
X/* 25-Jul-87 IBM */
X/* 09-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	conf()
X
X	Statics:	ytdef()		ytexca()	ytr1()
X			ytr2()		srconf()	endstate()
X			rrconf()	finddef()	addexca()
X			dotrans()	gettrans()	doitem()
X			getitem()	lsitem()
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
X#define realtok(s)	( toknum[(s)] )
X
Xstatic FILE *fconflict;			/* Where to send conflict messages */
Xstatic int sr,psr,rr;			/* Count of conflicts (p..=resolved) */
Xstatic int *yxdef;			/* Array of default reductions */
X					/* Size of cnstate */
X
Xtypedef struct intlist {
X    struct intlist *next;
X    int val;
X} INTLIST;
X
Xstatic INTLIST *yxexca;			/* List of exception PAIRS */
Xstatic int nnexca;			/* Number of list entries (2*pairs) */
X
Xstatic int txsym;
Xstatic int txfrom;
Xstatic int txto;
Xstatic int itst;
Xstatic int itlhs;
Xstatic int itrule;
Xstatic int itdposn;
Xstatic int comprule;			/* Rule just seen in state (real) */
X
Xvoid
Xconf()					/* Resolve conflicts */
X{
X    void getitem(),gettrans(),doitem(),dotrans(),endstate();
X    void yttable();
X    int ytdef(),ytexca(),ytr1(),ytr2();
X    int st;
X    INTLIST *l,*l2;
X
X    message("conf:");
X
X    ftrans=xopen(ntrans,"rb");
X    fshift=xopen(nshift,"wb");
X    if (o_verbose) {
X	foutput=xopen(noutput,"w");
X	fconflict=foutput;		/* Conflicts go with description */
X    }
X    else {
X	fconflict=stderr;		/* Conflicts go to stderr */
X    }
X    fitem=xopen(nitem,"rb");
X
X    yxdef=(int *)xalloc(cnstate*sizeof(int));
X
X    yxexca=NULL;
X    nnexca=0;				/* Exception table empty */
X
X    sr=psr=rr=0;
X    cnshift=0;				/* Count entries in fshift */
X
X    getitem();				/* Lookahead at files */
X    gettrans();
X
X    for (st=0; st <cnstate; ++st) {
X	if (o_verbose) fprintf(foutput,"state %u\n",st);
X	yxdef[st]=0;			/* Default action is error */
X	doitem(st);
X	dotrans(st);
X	endstate(st);
X	if (o_verbose) fprintf(foutput,"\n");
X    }
X    fprintf(fconflict,
X	"%u shift/reduce, %u reduce/reduce conflicts reported\n",
X	sr,rr);
X    fprintf(fconflict,
X	"(another %u shift/reduce conflicts resolved)\n",psr);
X
X    xclose(ftrans);
X    putw(-1,fshift);		/* Eof indicator */
X    xclose(fshift);
X    if (o_verbose) xclose(foutput);
X    xclose(fitem);
X
X    fytabc=xopen(nytabc,"a");
X    yttable(fytabc,ytdef,"yydef",cnstate,TABLEWIDTH);
X    yttable(fytabc,ytexca,"yyexca",nnexca,2);
X    yttable(fytabc,ytr1,"yyr1",cnrule,TABLEWIDTH);
X    yttable(fytabc,ytr2,"yyr2",cnrule,TABLEWIDTH);
X    xclose(fytabc);
X
X    xfree((char *)yxdef);
X    for (l=yxexca; l; l=l2) {
X	l2=l->next;
X	xfree((char *)l);
X    }
X}
X
Xstatic int
Xytdef(i)
Xint i;
X{
X    return yxdef[i];
X}
X
Xstatic int
Xytexca(i)			/* MUST be called from 0 consecutively */
Xint i;
X{
X    static INTLIST *l;
X
X    if (i)
X	return (l=l->next)->val;
X    else
X	return (l=yxexca)->val;
X}
X
Xstatic int
Xytr1(i)
Xint i;
X{
X    int j;
X
X    for (j=0; ruleseq[j] != i; ++j);
X    return valnont(rulesym[j]);
X}
X
Xstatic int
Xytr2(i)
Xint i;
X{
X    int j;
X
X    for (j=0; ruleseq[j] != i; ++j);
X    return lngrule(j);
X}
X
Xstatic int			/* Check that there is no conflict */
Xsrconf(tok,from,to)		/* Returns 1 shift not to be deleted */
Xint tok;
Xint from;
Xint to;
X{
X    int fail,delreduce,delshift;
X    int i,r;
X
X    delshift=delreduce=fail=0;
X    for (i=0; i<cnincon; ++i) {
X	if (ist[i] == from) {
X	    if (isbit(ila[i],tok)) {
X		r=irule[i];
X		trace(("check: tokassoc %u tokprec %u ruleprec %u\n",
X			tokassoc[tok],tokprec[tok],ruleprec[r]));
X		if (tokprec[tok] == 0 || ruleprec[r] == 0) {
X		    fail=1;
X		    delreduce=1;	/* Default is to shift */
X		}
X		else if (tokprec[tok] == ruleprec[r]) {
X		    switch (tokassoc[tok]) {
X			case LEFT:	/* Resolve by reduction */
X					delshift=1;
X					break;
X			case RIGHT:	/* Resolve by shift */
X					delreduce=1;
X					break;
X			case NONE:	/* Can't resolve - fall thru */
X					fail=1;
X			case NONASSOC:	/* Error - don't shift or reduce ! */
X					delshift=1;
X					delreduce=1;
X					break;
X		    }
X		}
X		else if (tokprec[tok] < ruleprec[r]) {
X		    delshift=1;
X		}
X		else {
X		    delreduce=1;
X		}
X		if (fail) {
X		    ++sr;
X		}
X		else {
X		    ++psr;
X		}
X		if (delreduce) {
X		    trace(("check: delete reduction\n"));
X		    clrbit(ila[i],tok);
X		}
X		if (fail || o_listall) {
X		    fprintf(fconflict,
X			"%u:s/r conflict (shift %u,reduce %u) on %s\n",
X			from,to,ruleseq[r],nametok(tok));
X		}
X	    }
X	}
X    }
X    return (delshift == 0);
X}
X
Xstatic void
Xendstate(st)
Xint st;
X{
X    void addexca();
X    void rrconf();
X    int finddef();
X    int idef,ifirst,ilast,i,j,k,r;
X
X    for (i=0; i<cnincon && ist[i]!=st; ++i);
X    ifirst=i;
X    for (i=ifirst; i<cnincon && ist[i]==st; ++i);
X    ilast=i-1;
X    trace(("endstate: from %u(%u) to %u(%u)\n",
X	ifirst,ist[ifirst],ilast,ist[ilast]));
X
X    if (ilast > ifirst) {		/* Is a complex state */
X					/* ie. >1 complete item */
X	rrconf(ifirst,ilast);		/* Resolve any rr conflict */
X
X	if (yxdef[st] != -2) {		/* No exception used yet(eg. accept) */
X	    yxdef[st]=-2;		/* Flag use of exception for state */
X	    addexca(-1,st);		/* Exception state */
X	}
X	idef=finddef(ifirst,ilast);	/* Find rule to use as default */
X
X	for (i=ifirst; i<=ilast; ++i) {	/* For all rules */
X	    if (i != idef) {		/* Apart from default */
X		r=irule[i];
X		for (k=0; k<cntok; ++k) {
X		    if (isbit(ila[i],k)) {
X			addexca(realtok(k),ruleseq[r]);
X					/* lookahead k -> reduce to r */
X			if (o_verbose) {
X			    fprintf(foutput,"\t%s\treduce %u\n",
X				nametok(k),ruleseq[r]);
X			}
X		    }
X		}
X	    }
X	}
X	addexca(-2,ruleseq[r=irule[idef]]);	/* default reduction */
X	if (o_verbose) fprintf(foutput,"\t.\treduce %u\n",ruleseq[r]);
X    }
X    else {				/* Is simple or inconsistent */
X					/* with only one complete item */
X
X	if (yxdef[st] == -2) {		/* Add default error or reduce */
X	    addexca(-2,comprule);	/* To exception list */
X	}
X	else {
X	    yxdef[st]=comprule;		/* No exceptions */
X	}
X	if (o_verbose) {
X	    if (comprule) {
X		fprintf(foutput,"\t.\treduce %u\n",comprule);
X	    }
X	    else {
X		fprintf(foutput,"\t.\terror\n");
X	    }
X	}
X    }
X}
X
Xstatic void				/* Resolve any rr conflict */
Xrrconf(ifirst,ilast)
Xint ifirst,ilast;			/* Range of incon table to check */
X{
X    int i,j,k;
X
X    for (k=0; k<cntok; ++k) {
X	trace(("rrconf: token %s\n",nametok(k)));
X	for (i=ifirst; i<=ilast; ++i) {
X	    trace(("rrconf: item %u\n",i));
X	    if (isbit(ila[i],k)) {
X		trace(("rrconf: item %u lookahead %s\n",i,nametok(k)));
X		for (j=ifirst; j<i; ++j) {
X		    trace(("rrconf: checking against item %u\n",j));
X		    if (isbit(ila[j],k)) {
X		        trace(("rrconf: conflict\n"));
X		        ++rr;
X		        fprintf(fconflict,
X			    "%u:r/r conflict (reduce %u, %u) on %s\n",
X			    ist[i],ruleseq[irule[i]],
X			    ruleseq[irule[j]],nametok(k));
X		        if (ruleseq[irule[i]] < ruleseq[irule[j]]) {
X			    trace(("rrconf: removing from %u\n",j));
X			    clrbit(ila[j],k);
X		        }
X		        else {	/* Default is to use earlier rule */
X			    trace(("rrconf: removing from %u\n",i));
X			    clrbit(ila[i],k);
X		        }
X		    }
X		}
X	    }
X	}
X    }
X}
X
Xstatic int			/* Find default reduction */
Xfinddef(ifirst,ilast)
Xint ifirst,ilast;			/* Index to rules in incon table */
X{
X    int most,count,idef,i,j;
X
X    most=0;
X    idef=ifirst;			/* Just in case all empty !! ?? */
X    for (i=ifirst; i<=ilast; ++i) {	/* For each rule */
X	count=0;
X	for (j=0; j<cntok; ++j) {	/* Count number of lookahead symbols */
X	    if (isbit(ila[i],j)) {
X		++count;
X	    }
X	}
X	if (count > most) {		/* Default is the one with the most */
X	    most=count;			/* Lookahead symbols */
X	    idef=i;
X	}
X    }
X    return idef;
X}
X
Xstatic void
Xaddexca(v1,v2)
Xint v1,v2;
X{
X    INTLIST *l,*l1,*l2;
X
X    for (l=yxexca; l && l->next; l=l->next);
X
X    l1=(INTLIST *)xalloc(sizeof(INTLIST));
X    l2=(INTLIST *)xalloc(sizeof(INTLIST));
X    if (l)
X	l->next=l1;
X    else
X	yxexca=l1;
X    l1->next=l2;
X    l2->next=NULL;
X    l1->val=v1;
X    l2->val=v2;
X    nnexca+=2;
X}
X
Xstatic void
Xdotrans(st)
Xint st;
X{
X    void gettrans();
X    int srconf();
X    int real,tok,lastsym;
X
X    trace(("dotrans:\n"));
X    lastsym=-1;				/* Don't do duplicate entries */
X    while (txsym != -1 && txfrom == st) {
X	if (txsym != lastsym) {
X	    lastsym=txsym;
X	    if (istok(txsym)) {
X		tok=valtok(txsym);
X		real=realtok(tok);
X		if (srconf(tok,txfrom,txto)) {	/* Shift is valid */
X		    if (real == ENDTOKEN) {	/* Shift on $end is accept */
X			if (o_verbose) {
X			    fprintf(foutput,"\t%s\taccept\n",nametok(tok));
X			}
X			yxdef[st]=-2;		/* Flag use of exception */
X			addexca(-1,st);		/* Set exception state */
X			addexca(real,-1);	/* $end -> Accept */
X		    }
X		    else {
X			if (o_verbose) {
X			    fprintf(foutput,"\t%s\tshift %u\n",
X				nametok(tok),txto);
X			}
X			++cnshift;
X			putw(real,fshift);	/* Token's real value */
X			putw(txfrom,fshift);	/* From state */
X			putw(txto,fshift);	/* To state */
X		    }
X		}
X	    }
X	    else {				/* Is nont */
X		if (o_verbose) {
X		    fprintf(foutput,"\t%s\tgoto %u\n",namesym(txsym),txto);
X		}
X	    }
X	}
X	gettrans();
X    }
X}
X
Xstatic void
Xgettrans()
X{
X    trace(("gettrans:\n"));
X    if ((txsym=getw(ftrans)) != -1 ) {	/* Symbol */
X	txfrom=getw(ftrans);		/* From state (sorted on this) */
X	txto=getw(ftrans);		/* To state */
X	(void)getw(ftrans);		/* Ignore rule */
X	(void)getw(ftrans);		/* Ignore dposn */
X	trace(("gettrans: txsym=%u txfrom=%u txto=%u\n",txsym,txfrom,txto));
X    }
X}
X
Xstatic void
Xdoitem(st)
Xint st;
X{
X    void getitem(),lsitem();
X
X    trace(("doitem:\n"));
X    comprule=0;				/* No complete item found yet */
X    while (itst != -1 && itst == st) {
X	if (o_verbose) {
X	    lsitem(itrule,itdposn,itlhs);
X	}
X	if (itdposn == 0) {		/* Complete item */
X	    comprule=ruleseq[itrule];	/* Remember real rule for endstate() */
X	}
X	getitem();
X    }
X    if (o_verbose) fprintf(foutput,"\n");
X}
X
Xstatic void
Xgetitem()
X{
X    trace(("getitem:\n"));
X    if ((itst=getw(fitem)) != -1) {	/* State containing item */
X	itlhs=getw(fitem);		/* LHS Symbol (NB. Not valnont()) */
X	itrule=getw(fitem);		/* Rule number */
X	itdposn=getw(fitem);		/* Distinguished posn (0=complete) */
X	trace(("getitem: itst=%u itlhs=%u itrule=%u itdposn=%u\n",
X		itst,itlhs,itrule,itdposn));
X    }
X}
X
Xstatic void
Xlsitem(rule,dposn,lhs)
Xint rule,dposn,lhs;
X{
X    int i,end;
X
X    end=lngrule(rule)+1;
X    dposn=dposn ? dposn : end;
X    fprintf(foutput,"\t%s\t: ",namesym(lhs));
X    for (i=1; i<dposn; ++i) {
X	fprintf(foutput,"%s ",namesym(rhs[rulerhs[rule]+i-1]));
X    }
X    fprintf(foutput,"_ ");
X    for (i=dposn; i<end; ++i) {
X	fprintf(foutput,"%s ",namesym(rhs[rulerhs[rule]+i-1]));
X    }
X    if (dposn == end) {		/* Complete items - append rule sequence */
X	fprintf(foutput,"\t(%u)",ruleseq[rule]);
X    }
X    fprintf(foutput,"\n");
X}
X
END_OF_FILE
if test 11155 -ne `wc -c <'yaconf.c'`; then
    echo shar: \"'yaconf.c'\" unpacked with wrong size!
fi
# end of 'yaconf.c'
fi
if test -f 'yacpm.h' ; then
  echo shar: Will not clobber existing file \"'yacpm.h'\"
else
echo shar: Extracting \"'yacpm.h'\" \( 1856 characters \)
sed "s/^X//" >'yacpm.h' <<'END_OF_FILE'
X/* 08-Jul-89 Not recently tested */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X#define SYSTEM	 "CPM-80 (file,overlays)"
X#define CPM
X
X#define PLINKII			/* CPM-80 with PLINK-II overlays */
X
X/* timer not implemented under CPM */
Xtypedef long clock_t;
X#define	clock()		(0l)
X
X#define TTYHEAD	<sgtty.h>	/* define only if isatty() needs sgtty.h */
X
X#define	iseofchar(c)	( c == EOF || c == 0x1a )	/* ctrl-Z */
X
X#define BITSTR	unsigned int	/* Type of word used for bit strings */
X
X#define SORTTABLE	3000	/* size of pointer table in txsort() */
X				/* larger -> longer runs */
X
X#define	rdstrch(f)	getc(f)
X#define	wrstrch(u,f)	putc(u,f)
X
X/* set PATHSEPARATOR to null string "" if paths not implemented */
X#ifndef PATHSEPARATOR
X#define	PATHSEPARATOR	""
X#endif
X
X/* leave TMPENVPATH undefined if compiler can't access environment */
X
X/* set TMPDEFPATH to null string "" (current directory) if no paths */
X#ifndef TMPDEFPATH			/* if not defined on compile line */
X#define TMPDEFPATH	""		/* path to use if not in environment */
X#endif
X
X/* leave SKELENVPATH undefined if compiler can't access environment */
X
X/* set SKELDEFPATH to null string "" (current directory) if no paths */
X#ifndef SKELDEFPATH			/* if not defined on compile line */
X#define SKELDEFPATH	""		/* path to use if not in environment */
X#endif
X#ifndef SKELDEFNAME			/* if not defined on compile line */
X#define SKELDEFNAME	"yaccpar"	/* path to use if not in environment */
X#endif
X
X#ifndef YTABHDEFNAME			/* if not defined on compile line */
X#define	YTABHDEFNAME	"ytab.h"
X#endif
X#ifndef YTABCDEFNAME			/* if not defined on compile line */
X#define	YTABCDEFNAME	"ytab.c"
X#endif
X#ifndef YOUTDEFNAME			/* if not defined on compile line */
X#define	YOUTDEFNAME	"youtput"
X#endif
END_OF_FILE
if test 1856 -ne `wc -c <'yacpm.h'`; then
    echo shar: \"'yacpm.h'\" unpacked with wrong size!
fi
# end of 'yacpm.h'
fi
if test -f 'yadefs.h' ; then
  echo shar: Will not clobber existing file \"'yadefs.h'\"
else
echo shar: Extracting \"'yadefs.h'\" \( 11226 characters \)
sed "s/^X//" >'yadefs.h' <<'END_OF_FILE'
X/* Yadefs.h	15-Oct-86 */
X/* 01-Aug-87 IBM */
X/* 25-Mar-88 VAXVMS */
X/* 07-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X#include "yavers.h"
X
X#include "yasystem.h"
X
X#ifdef STDLIBHEAD
X#include STDLIBHEAD
X#endif
X
X#ifdef STRINGHEAD
X#include STRINGHEAD
X#endif
X
X#define DATAMODEL ( sizeof(char *) > 2 ? "large" : "small" )
X#define CODEMODEL ( sizeof(char (*)()) > 2 ? "large" : "small" )
X
X#ifdef	PLINKII
X#define PREAMBLE "run "			/* Used by usage message on init */
X#else
X#define PREAMBLE ""
X#endif
X
X/*
X#define	BITMACRO
X*/
X
X#ifdef	TRACE				/* Strip off outer parentheses */
X#define	trace(x)	printf x
X#else
X#define	trace(x)
X#endif	/* TRACE */
X
X#ifdef	DEFINE
X#define DEFMAC
X#else
X#define	DEFMAC	extern
X#endif	/* DEFINE */
X
X#define	DEF0	extern		/* Phase0 declarations visible to all phases */
X
X#ifdef	DEFINE
X#ifdef	PHASE0
X#undef	DEF0
X#define	DEF0			/* But only define in phase 0 itself */
X#endif	/* PHASE0 */
X#endif	/* DEFINE */
X
X/*		****** PHASE0 ****** ****** PHASE0 ******		*/
X
X/*			****** Bitmap Stuff ******			*/
X
X#define BITBYTE	sizeof(BITSTR)	/* Length in bytes of BITSTR */
X#define BITLNG	(BITBYTE * 8)	/* Length in bits of BITSTR */
X
X#ifdef	BITMACRO
X
X#define	isbit(s,n)	( ((s)[(n) / BITLNG]) &  (1 << ((n) % BITLNG)) )
X#define setbit(s,n)	( ((s)[(n) / BITLNG]) |= (1 << ((n) % BITLNG)) )
X#define clrbit(s,n)	( ((s)[(n) / BITLNG]) &= ~(1 << ((n) % BITLNG)) )
X#define	sizebit(n)	( (n-1)/BITLNG+1 )
X#define alcbit(n)	( (BITSTR *)xalloc(sizebit(n)*BITBYTE) )
X
X#else
X
Xint isbit();
Xvoid setbit();
Xvoid clrbit();
Xint sizebit();
XBITSTR *alcbit();
X
X#endif
X
Xvoid zerobit();
Xint orbit();
Xint andbit();
Xint eqbit();
Xvoid copybit();
X
X/*		****** Variously used constants ******			*/
X
X#define	ABORT	1
X#define	FATAL	2
X#define	WARNING	3
X
X#define NONE		1
X#define TOKEN		2
X#define	LEFT		3
X#define	RIGHT		4
X#define	NONASSOC	5
X#define TYPE		6
X#define	NONT		7
X
X#define FIRSTTOKEN	256		/* First non-literal token */
X#define	ENDTOKEN	0		/* Endmarker */
X
X#define TABLEWIDTH	10		/* Width of ytab.c tables */
X
X#define	YXFLAG		-1000		/* Empty entry in yxact[] */
X
X/*		***** Declare file names and handles *****		*/
X
X#define	nytabh		YTABHDEFNAME
X#define	nytabc		YTABCDEFNAME
X#define noutput		YOUTDEFNAME
X#define tnaction	"yaction.$$$"
X#define tnstring	"ystring.$$$"
X#define	tnsymbol	"ysymbol.$$$"
X#define tnrule		"yrule.$$$"
X#define	tnrhs		"yrhs.$$$"
X#define tnitem		"yitem.$$$"
X#define tngoto		"ygoto.$$$"
X#define tnshift		"yshift.$$$"
X#define tntr2		"ytr2.$$$"
X#define tntrans		"ytrans.$$$"
X
X/* 		****** function return values ******			*/
X
Xchar *xalloc();
Xchar *xrealloc();
Xvoid xfree();
Xvoid errmsg();
Xvoid bug();
Xvoid where();
Xchar *itoa();
XFILE *xopen();
Xvoid xclose();
X
X/* 		****** Storage declaration/definition ******		*/
X
XDEF0 int	o_verbose;	/* Option - generate youtput */
XDEF0 int	o_define;	/* Option - copy definitions to ytabh */
XDEF0 int	o_debug;	/* Option - describe what yacc is doing */
XDEF0 int	o_yydebug;	/* Option - debugging on is default */
XDEF0 int	o_linenum;	/* Option - include line numbers in output */
XDEF0 int	o_listall;	/* Option - list resolved conflicts as well */
XDEF0 char	*o_inname;	/* Option - input file name (NULL -> stdin) */
X
X/* Declare pointers to names of temporary files (dynamically allocated) */
X
XDEF0 char *nyaccpar;
XDEF0 char *naction;
XDEF0 char *nstring;
XDEF0 char *nsymbol;
XDEF0 char *nrule;
XDEF0 char *nrhs;
XDEF0 char *nitem;
XDEF0 char *ngoto;
XDEF0 char *nshift;
XDEF0 char *ntr2;
XDEF0 char *ntrans;
X
XDEF0 char *g_tmppath;		/* Temporary file path */
X
XDEF0 FILE	*finput,	/* Yacc input file containing grammar */
X		*fyaccpar,	/* Yacc input model parser */
X		*fytabh,	/* Yacc output definitions (for lex) */
X		*fytabc,	/* Yacc output (parser,tables,actions) */
X		*foutput,	/* Yacc output verbose description */
X		*faction,	/* Temporary - actions */
X		*fstring,	/* Temporary - strings */
X		*fsymbol,	/* Temporary - symbols */
X		*frule,		/* Temporary - rules */
X		*frhs,		/* Temporary - rule rhs */
X		*fitem,		/* Temporary - items */
X		*fshift,	/* Temporary - shift entries */
X		*fgoto,		/* Temporary - goto entries */
X		*ftr2,		/* Temporary - transitions sorted by rule */
X		*ftrans;	/* Temporary - transitions */
X
XDEF0 int cnwarning;		/* Count of warnings in input */
XDEF0 int cnfatal;		/* Count of fatal errors in input */
XDEF0 int cnstr;			/* Size of string area */
XDEF0 int cnrule;		/* Number of rules */
XDEF0 int cnrhs;			/* Number of symbols in rhs of rules */
XDEF0 int cnnont;		/* Number of non-terminals */
XDEF0 int cntok;			/* Number of tokens (literal & non-literal) */
XDEF0 int bstok;			/* 1st value for non-literal tokens */
XDEF0 int bsnont;		/* 1st value for non-terminals */
X
XDEF0 int start;			/* Symbol sequence number of start nont */
X
XDEF0 int cnstate;		/* Count of states */
XDEF0 int cnitem;		/* Count of items */
XDEF0 int cnincon;		/* Count of inconsistent items in states */
XDEF0 int cncxst;		/* Count of complex states */
XDEF0 int cncxit;		/* Count of complete items in complex states */
XDEF0 int cnntx;			/* Count of nonterminal transitions */
XDEF0 int cnttx;			/* Count of token transitions */
XDEF0 int cnrtx;			/* Count of transitions with rules in file */
XDEF0 int cnshift;		/* Count of shift entries */
XDEF0 int cngo;			/* Count of goto entries */
X
Xtypedef struct ntxtab {
X    int nont;			/* Transition on nonterminal */
X    int from;			/* From state */
X    int to;			/* To state */
X} NTXTAB;
X
XDEF0 NTXTAB *ntxtab;		/* Table of nonterminal transitions */
X				/* NB. table of entries NOT pointers */
X
XDEF0 BITSTR **incl;		/* Table indexed by ntx of includes relation */
X				/* Of lists of ntx */
XDEF0 BITSTR **lback;		/* Table indexed by inconsistent item */
X				/* Of lists of ntx in lookback relation */
X
XDEF0 BITSTR **dread;		/* Table indexed by state of direct reads */
X				/* Vector indexed by tokens */
X
XDEF0 int *ist;			/* Inconsistent complete items - state */
XDEF0 int *ilhs;			/* Inconsistent complete items - lhs nont */
XDEF0 int *irule;		/* Inconsistent complete items - rule */
XDEF0 BITSTR **ila;		/* Inconsistent complete items - lookahead */
X				/* (vector indexed by tokens) */
X
X#ifdef CPM
X#define DISTACKSIZE	50
X#else
X#define DISTACKSIZE	200
X#endif
X
X#define INFINITY	DISTACKSIZE+1	/* Doen't need to be greater */
X					/* Musn't be negative on int compare */
X
XDEF0 BITSTR **work;		/* Array indexed by ntx of work vectors */
X				/* for lookahead. Vector indexed by token */
X				/* Contains either "reads" or "follows" */
X
XDEF0 int dmax,			/* Length of din */
X	 *din,			/* Array used by traverse */
X	 *stack,		/* Stack used by traverse */
X	 *sp,			/* Stack pointer (empty=stack-1) */
X	 depth;			/* Stack depth (empty=0) */
X
X
XDEF0 void (*dicopy)();		/* Function to copy vector */
XDEF0 void (*diunion)();		/* Function to union two vectors */
XDEF0 int  (*direln)();		/* Function to return relation */
X
X
X/*		****** PHASE1 ****** ****** PHASE1 ******		*/
X
X#ifdef	PHASE1
X
X#define	PROMPT	".."		/* Prompt tty for input */
X
X#define	ENDSTR	"\032"		/* End of file as a string !!! */
X				/* (Used to ccopy() until EOF) */
X
X#define DEFINITIONS	0	/* Values for section */
X#define	RULES		1	/* (Communicate between parser and lex) */
X#define	TAIL		2
X
X#define	BUFLNG	256			/* Lexical analyzer buffer */
X
X#define	STACKSIZE	128		/* Parser stack length */
X
X#define HASHSIZE  141			/* should be prime */
X#define HASHIFT 4
X#define HASHMASK 0x1f
X
X/*		****** Values for toknum ******				*/
X
X#define	NOTOKEN		-1		/* Value used when no token specd */
X
X#define	ENDNAME		"$end"		/* Name of endmarker */
X#define	ACCEPTNAME	"$accept"	/* Name of accept symbol */
X#define	ERRORNAME	"error"		/* Name of error symbol */
X
X#define NOTYPE		NULL		/* Value used when no union type */
X
X/* 		****** Data structure definitions ******		*/
X
Xtypedef struct symbol {			/* symbol table entry */
X    char *name;				/* description (string) */
X    struct symbol *lsym;		/* next symbol in link chain */
X    char kind;				/* TOKEN,NONT */
X    char assoc;				/* NONE,LEFT,RIGHT,NONASSOC */
X    int prec;				/* 0 = none */
X    int toknum;				/* 0=EOF,1-256=literal,>256=rest */
X    char *type;				/* Union type (NOTYPE=none) */
X    struct rule *rule;			/* Rule list for nont(NULL=none) */
X} SYMBOL;
X
Xtypedef struct rule {			/* Rule list entry */
X    struct symbol *sym;			/* LHS nonterminal */
X    int prec;				/* Precedence */
X    int seq;				/* Sequence number */
X    struct list *list;			/* List of RHS symbols */
X    struct rule *next;			/* Next rule in list */
X} RULE;
X
Xtypedef struct list {			/* List of symbols */
X    struct symbol *sym;
X    struct list *next;
X} LIST;
X
X/* 		****** Storage declaration/definition ******		*/
X
XDEFMAC SYMBOL *send;			/* Define end marker */
XDEFMAC SYMBOL *sstart;			/* Define start symbol */
XDEFMAC SYMBOL *shead;			/* Head of thread thru symbols */
X
XDEFMAC int ch;				/* Nxtchar() read */
X
XDEFMAC int section;			/* Set by parser routines */
XDEFMAC int nextrule;			/* Sequence number to be used by */
X					/* nextrule - used as case number of */
X					/* action as well */
XDEFMAC int g_offset;			/* Offset of element from beginning */
X					/* of rule being parsed */
X					/* (0 = before 1st element) */
X
XDEFMAC SYMBOL *g_cid;			/* Left nont of rule being parsed */
XDEFMAC RULE *g_rule;			/* Rule being parsed */
X
XDEFMAC int g_typeon;			/* Type checking has been activated */
X
XDEFMAC int curprec;			/* Used by parser routines */
XDEFMAC char *curtype;
XDEFMAC int command;
X
X#endif	/* PHASE1 */
X
X#ifdef	PHASE2
X
X/* 		****** Data structure definitions ******		*/
X
Xtypedef struct state {			/* State list entry */
X    int num;				/* Unique sequence number for state */
X    struct item *item;			/* Head of item list of this state */
X    struct item *empty;			/* List of empty items in closure */
X    struct state *next;
X} STATE;
X
Xtypedef struct item {			/* Item list entry */
X    int rule;				/* Index to rule table */
X    int dposn;				/* Distinguished position */
X					/* (0=complete,1=before 1st symbol) */
X    struct item *next;
X} ITEM;
X
Xtypedef struct trans {			/* Transition list entry */
X    int sym;				/* Sequence number of symbol */
X    struct item *item;			/* Item list to go to */
X    struct trans *next;
X} TRANS;
X
X/*		****** Macro definitions ******			*/
X
X#define	iscomplete(it)	( (it)->dposn == 0 )
X#define	rhssym(it,i)	( rhs[rulerhs[(it)->rule]+i-1] )
X#define	dsym(it)	( rhssym((it),(it)->dposn) )
X
X#define	lngrule(rule)	( rulerhs[(rule)+1] - rulerhs[(rule)] )
X
X#define	istok(sym)	( (sym) < cntok )
X#define	valtok(sym)	( sym )
X#define	isnont(sym)	( (sym) >= cntok )
X#define	valnont(sym)	( (sym) - cntok )
X#define	namenont(nont)	( strarea + nontstr[(nont)] )
X#define	nametok(tok)	( strarea + tokstr[(tok)] )
X#define	namesym(sym)	( isnont(sym) ? namenont((sym)-cntok) : nametok(sym) )
X
X/* 		****** Storage declaration/definition ******		*/
X
XDEFMAC BITSTR *nullable;	/* Bit string of nullable nont */
XDEFMAC BITSTR **first;		/* Array of first bit strings for nont */
X
XDEFMAC char *strarea;
XDEFMAC int *tokstr;
XDEFMAC int *toknum;
XDEFMAC int *tokprec;
XDEFMAC int *tokassoc;
XDEFMAC int *nontstr;
XDEFMAC int *nontrule;
XDEFMAC int *rulesym;
XDEFMAC int *ruleseq;
XDEFMAC int *ruleprec;
XDEFMAC int *rulerhs;
XDEFMAC int *rhs;
X
X#endif	/* PHASE2 */
X
END_OF_FILE
if test 11226 -ne `wc -c <'yadefs.h'`; then
    echo shar: \"'yadefs.h'\" unpacked with wrong size!
fi
# end of 'yadefs.h'
fi
if test -f 'yafdef.c' ; then
  echo shar: Will not clobber existing file \"'yafdef.c'\"
else
echo shar: Extracting \"'yafdef.c'\" \( 1827 characters \)
sed "s/^X//" >'yafdef.c' <<'END_OF_FILE'
X/* Yafdef.c	21-Jan-87	Parser functions used in defs only */
X/* 22-Jul-87 */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	docommand()	setprec()	setassoc()
X			settype()
X*/
X
X#include <stdio.h>
X
X#define PHASE1
X
X#include "yadefs.h"
X
Xvoid
Xdocommand(sym,toknum)
XSYMBOL *sym;			/* Symbol is identifier or literal */
Xint toknum;			/* Token number */
X{
X    void settok(),setnum(),setprec(),setassoc(),settype(),setnont();
X
X    switch (command) {
X	case TOKEN:	settok(sym,toknum);
X			settype(sym,curtype);
X			break;
X	case LEFT:
X	case RIGHT:
X	case NONASSOC:
X			settok(sym,toknum);
X			setprec(sym,curprec);
X			setassoc(sym,command);
X			settype(sym,curtype);
X			break;
X	case TYPE:
X			setnont(sym);
X			settype(sym,curtype);
X			break;
X	default:
X			bug("Docommand");
X			break;
X    }
X}
X
Xvoid
Xsetprec(sym,prec)
XSYMBOL *sym;
Xint prec;
X{
X    if (sym->prec && sym->prec != prec) {
X	errmsg("Can't redefine precedence",FATAL);
X    }
X    else {
X	sym->prec=prec;
X    }
X}
X
Xvoid
Xsetassoc(sym,assoc)
XSYMBOL *sym;
Xint assoc;
X{
X    if (sym->assoc != NONE && sym->assoc != assoc) {
X	errmsg("Can't redefine associativity",FATAL);
X    }
X    else {
X	sym->assoc=assoc;
X    }
X}
X
Xvoid
Xsettype(sym,type)
XSYMBOL *sym;
Xchar *type;
X{
X    if (type != NOTYPE) {
X	if (sym->type != NOTYPE) {
X	    if (sym->type != type) {
X		errmsg("Can't redefine type",FATAL);
X	    }
X	    /* else same so leave */
X	}
X	else {
X	    sym->type=type;
X	}
X    }
X    /* else leave it alone whether sym->type is NOTYPE or not */
X    /* ie. allows %token <type> sym then later %left sym without type */
X
X    /* this isn't necessary for prec and assoc because %token can't set */
X    /* either of these, and setprec/setassoc aren't called for %token */
X}
X
END_OF_FILE
if test 1827 -ne `wc -c <'yafdef.c'`; then
    echo shar: \"'yafdef.c'\" unpacked with wrong size!
fi
# end of 'yafdef.c'
fi
if test -f 'yafirst.c' ; then
  echo shar: Will not clobber existing file \"'yafirst.c'\"
else
echo shar: Extracting \"'yafirst.c'\" \( 3091 characters \)
sed "s/^X//" >'yafirst.c' <<'END_OF_FILE'
X/* Yafirst.c	29-Oct-86	Compute nullable and first for nonterminals */
X/* 25-Jul-87 IBM */
X/* 09-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	frfirst()	mkfirst()
X
X	Statics:	[dpfirst(),dpnbit() - TRACE]
X*/
X
X#include <stdio.h>
X
X#define	PHASE2
X
X#include "yadefs.h"
X
Xvoid
Xfrfirst()
X{
X    int n;
X
X    message("frfirst:");
X
X    for (n=0; n <cnnont; ++n) {
X	xfree((char *)first[n]);
X    }
X    xfree((char *)first);
X}
X
Xvoid
Xmkfirst()
X{
X#ifdef TRACE
X    void dpnbit(),dpfirst();
X#endif
X    int added;
X    int i,n,n2,r;
X
X    message("mkfirst:");
X
X    nullable=alcbit(cnnont);
X    zerobit(nullable,cnnont);
X
X    first=(BITSTR **)xalloc(cnnont*sizeof(BITSTR *));
X    for (n=0; n <cnnont; ++n) {
X	first[n]=alcbit(cnnont);
X	zerobit(first[n],cnnont);
X	setbit(first[n],n);		/* Nont is in its own first list */
X    }
X
X    do {				/* Iterative for transitive closure */
X	trace(("mkfirst: iteration\n"));
X#ifdef TRACE
X	dpfirst();
X#endif /* TRACE */
X
X	added=0;
X	for (n=0; n < cnnont; ++n) {			/* For all nont */
X	    for (r=nontrule[n]; r<nontrule[n+1]; ++r) {	/* For all its rules */
X		i=rulerhs[r];				/* For FIRST rhs sym */
X		if (i < rulerhs[r+1] &&			/* Rule not empty */
X			rhs[i] >= cntok) {		/* Nont */
X		    n2=rhs[i]-cntok;
X		    if (!isbit(first[n],n2)) {
X			trace(("mkfirst: Before adding %s to first %s\n",
X				namenont(n2),namenont(n)));
X#ifdef TRACE
X			dpnbit(first[n]);
X#endif
X			setbit(first[n],n2);
X			++added;
X			trace(("mkfirst: After adding %s to first %s\n",
X				namenont(n2),namenont(n)));
X#ifdef TRACE
X			dpnbit(first[n]);
X#endif
X		    }
X
X		    /* Merge first lists regardless - rhs may already be in */
X		    /* first list but its own first list may have changed */
X
X		    added+=orbit(first[n],first[n2],cnnont);
X		}
X	    }
X	}
X    } while (added);
X
X    do {
X	added=0;
X	for (n=0; n < cnnont; ++n) {			/* For all nont */
X	    for (r=nontrule[n]; r<nontrule[n+1]; ++r) {	/* For all its rules */
X		i=rulerhs[r];				/* For each rhs sym */
X		while (i < rulerhs[r+1] &&		/* Not yet at end */
X		       rhs[i] >= cntok  &&		/* And nont */
X		       isbit(nullable,rhs[i]-cntok)) {	/* Which is nullable */
X 			    ++i;			/* Look at next rhs */
X		}
X
X		if (i == rulerhs[r+1]) {	/* End, so whole rhs =>empty */
X		    if (!isbit(nullable,n)) {
X			setbit(nullable,n);
X			++added;
X			trace(("mkfirst: Setting nullable %s\n",namenont(n)));
X		    }
X		}
X	    }
X	}
X     } while (added);
X
X#ifdef TRACE
X    dpfirst();
X#endif /* TRACE */
X}
X
X#ifdef TRACE
Xstatic void
Xdpfirst()
X{
X    void dpnbit();
X    int n;
X
X    printf("Nullable =>");
X    dpnbit(nullable);
X
X    for (n=0; n < cnnont; ++n) {			/* For all nont */
X	printf("%s first => ",namenont(n));
X	dpnbit(first[n]);
X    }
X}
X
Xstatic void
Xdpnbit(s)
XBITSTR *s;
X{
X    int i;
X
X    for (i=0; i<sizebit(cnnont) ; ++i) {
X	printf("%04x",s[i]);
X    }
X    printf("  ");
X    for (i=0; i<cnnont; ++i) {
X	if (isbit(s,i)) {
X	    printf("%s ",strarea+nontstr[i]);
X	}
X    }
X    printf("\n");
X}
X
X#endif /* TRACE */
X
END_OF_FILE
if test 3091 -ne `wc -c <'yafirst.c'`; then
    echo shar: \"'yafirst.c'\" unpacked with wrong size!
fi
# end of 'yafirst.c'
fi
if test -f 'yafrin.c' ; then
  echo shar: Will not clobber existing file \"'yafrin.c'\"
else
echo shar: Extracting \"'yafrin.c'\" \( 522 characters \)
sed "s/^X//" >'yafrin.c' <<'END_OF_FILE'
X/* Yafrin.c	04-Dec-86 */
X/* 09-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	frincon()
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xvoid
Xfrincon()
X{
X    int i;
X
X    message("frincon:");
X
X    xfree((char *)ist);
X    xfree((char *)irule);
X    for (i=0; i<cnincon; ++i) {
X	if (ila[i]) {
X	    xfree((char *)ila[i]);
X	}
X    }
X    xfree((char *)ila);
X}
X
END_OF_FILE
if test 522 -ne `wc -c <'yafrin.c'`; then
    echo shar: \"'yafrin.c'\" unpacked with wrong size!
fi
# end of 'yafrin.c'
fi
if test -f 'yafrprec.c' ; then
  echo shar: Will not clobber existing file \"'yafrprec.c'\"
else
echo shar: Extracting \"'yafrprec.c'\" \( 464 characters \)
sed "s/^X//" >'yafrprec.c' <<'END_OF_FILE'
X/* Yafrprec.c	04-Dec-86 */
X/* 09-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	frprec()
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xvoid
Xfrprec()
X{
X    message("frprec:");
X
X    xfree((char *)ruleprec);
X    xfree((char *)tokprec);
X    xfree((char *)tokassoc);
X    xfree((char *)toknum);
X}
X
END_OF_FILE
if test 464 -ne `wc -c <'yafrprec.c'`; then
    echo shar: \"'yafrprec.c'\" unpacked with wrong size!
fi
# end of 'yafrprec.c'
fi
if test -f 'yafrreln.c' ; then
  echo shar: Will not clobber existing file \"'yafrreln.c'\"
else
echo shar: Extracting \"'yafrreln.c'\" \( 541 characters \)
sed "s/^X//" >'yafrreln.c' <<'END_OF_FILE'
X/* Yafrreln.c	04-Dec-86 */
X/* 09-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	frreln()
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xvoid
Xfrreln()
X{
X    int i;
X
X    message("frreln:");
X
X    for (i=0; i <cnntx; ++i) {
X	xfree((char *)incl[i]);
X    }
X    xfree((char *)incl);
X    for (i=0; i <cnincon; ++i) {
X	xfree((char *)lback[i]);
X    }
X    xfree((char *)lback);
X}
X
END_OF_FILE
if test 541 -ne `wc -c <'yafrreln.c'`; then
    echo shar: \"'yafrreln.c'\" unpacked with wrong size!
fi
# end of 'yafrreln.c'
fi
if test -f 'yafrtx.c' ; then
  echo shar: Will not clobber existing file \"'yafrtx.c'\"
else
echo shar: Extracting \"'yafrtx.c'\" \( 471 characters \)
sed "s/^X//" >'yafrtx.c' <<'END_OF_FILE'
X/* Yafrtx.c	04-Dec-86 */
X/* 09-Jul-89 ZTC*/
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	frtx()
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xvoid
Xfrtx()
X{
X    int i;
X
X    message("frtx:");
X
X    xfree((char *)ntxtab);
X    for (i=0; i<cnstate; ++i) {
X	xfree((char *)dread[i]);
X    }
X    xfree((char *)dread);
X}
X
END_OF_FILE
if test 471 -ne `wc -c <'yafrtx.c'`; then
    echo shar: \"'yafrtx.c'\" unpacked with wrong size!
fi
# end of 'yafrtx.c'
fi
if test -f 'yafrule.c' ; then
  echo shar: Will not clobber existing file \"'yafrule.c'\"
else
echo shar: Extracting \"'yafrule.c'\" \( 575 characters \)
sed "s/^X//" >'yafrule.c' <<'END_OF_FILE'
X/* Yafrule.c	21-Jan-87	Parser functions used in rules only */
X/* 22-Jul-87 IBM */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	precok()
X*/
X
X#include <stdio.h>
X
X#define PHASE1
X
X#include "yadefs.h"
X
Xint
Xprecok(sym)
XSYMBOL *sym;
X{
X    if (sym->kind == TOKEN) {
X	if (sym->prec == 0) {
X	    errmsg("token has no assigned precedence",FATAL);
X	}
X    }
X    else {
X	errmsg("%prec must specify token",FATAL);
X    }
X    return sym->prec;
X}
X
END_OF_FILE
if test 575 -ne `wc -c <'yafrule.c'`; then
    echo shar: \"'yafrule.c'\" unpacked with wrong size!
fi
# end of 'yafrule.c'
fi
if test -f 'yafunc.c' ; then
  echo shar: Will not clobber existing file \"'yafunc.c'\"
else
echo shar: Extracting \"'yafunc.c'\" \( 1730 characters \)
sed "s/^X//" >'yafunc.c' <<'END_OF_FILE'
X/* Yafunc.c	21-Jan-87	Parser functions used in defs,rules & tail */
X/* 25-Jul-87 IBM */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	settok()	setnont()	addlist()
X			addrule()
X*/
X
X#include <stdio.h>
X
X#define PHASE1
X
X#include "yadefs.h"
X
Xvoid
Xsettok(sym,toknum)
XSYMBOL *sym;
Xint toknum;
X{
X    if (sym->kind == NONE) {
X	sym->kind=TOKEN;
X	sym->assoc=NONE;
X	sym->prec=0;
X	sym->type=NOTYPE;
X	sym->toknum=(toknum == NOTOKEN) ? bsnont++ : toknum;
X	++cntok;
X    }
X    else {
X	if (sym->kind == TOKEN) {
X	    if (toknum != NOTOKEN && sym->toknum != toknum) {
X		errmsg("Can't redefine token number",FATAL);
X	    }
X	}
X	else {
X	    errmsg("Can't redeclare symbol as token",FATAL);
X	}
X    }
X}
X
Xvoid
Xsetnont(sym)
XSYMBOL *sym;
X{
X    if (sym->kind == NONE) {
X	sym->kind=NONT;
X	sym->type=NOTYPE;
X	sym->rule=NULL;
X	++cnnont;
X    }
X    else {
X	if (sym->kind != NONT) {
X	    errmsg("Can't redeclare symbol as nonterminal",FATAL);
X	}
X    }
X}
X
Xvoid
Xaddlist(rule,sym)
XRULE *rule;
XSYMBOL *sym;
X{
X    LIST *list,*last;
X
X    list=(LIST *)xalloc(sizeof(LIST));
X    ++cnrhs;				/* Track number of symbols in lists */
X    list->sym=sym;
X    list->next=NULL;
X
X    last=rule->list;
X    while (last && last->next) {
X	last=last->next;
X    }
X
X    if (last) {				/* Link to end of list */
X	last->next=list;
X    }
X    else {			/* First entry, so head of list */
X	rule->list=list;
X    }
X}
X
XRULE *addrule()
X{
X    RULE *rule;
X
X    rule=(RULE *)xalloc(sizeof(RULE));
X    rule->list=NULL;			/* Empty right side */
X    rule->prec=NULL;			/* No precedence is default */
X					/* sym,seq,next filled in later */
X    return rule;
X}
X
END_OF_FILE
if test 1730 -ne `wc -c <'yafunc.c'`; then
    echo shar: \"'yafunc.c'\" unpacked with wrong size!
fi
# end of 'yafunc.c'
fi
if test -f 'yagoto.c' ; then
  echo shar: Will not clobber existing file \"'yagoto.c'\"
else
echo shar: Extracting \"'yagoto.c'\" \( 1400 characters \)
sed "s/^X//" >'yagoto.c' <<'END_OF_FILE'
X/* Yagoto.c 15-Dec-86	Make goto file from sorted nonterminal transitions */
X/* 25-Jul-87 IBM */
X/* 30-Nov-88 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	mkgoto()
X
X	Statics:	gcmp()
X
X	Uses:		qsort()
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xvoid
Xmkgoto()
X{
X    void qsort();
X    int gcmp();
X    int i;
X
X    message("mkgoto:");
X
X    fgoto=xopen(ngoto,"wb");
X
X    trace(("mkgoto: cnntx=%d sizeof(NTXTAB)=%d *=%d\n",
X	cnntx,sizeof(NTXTAB),cnntx*sizeof(NTXTAB) ));
X
X#ifdef TRACE
X    for (i=0; i<cnntx; ++i) {
X	trace(("mkgoto:ntxtab[i] from %u\tto %u\t nont %u\t%s\n",
X	ntxtab[i].from,ntxtab[i].to,ntxtab[i].nont,namenont(ntxtab[i].nont)));
X    }
X#endif
X
X    qsort(ntxtab,cnntx,sizeof(NTXTAB),gcmp);
X
X    for (i=0; i<cnntx; ++i) {
X	trace(("goto: on %s\tfrom %d to %d\n",
X		namenont(ntxtab[i].nont),ntxtab[i].from,ntxtab[i].to));
X	putw(ntxtab[i].nont,fgoto);	/* Output real value */
X	putw(ntxtab[i].from,fgoto);
X	putw(ntxtab[i].to,fgoto);
X    }
X    putw(-1,fgoto);
X    xclose(fgoto,ngoto);
X}
X
Xstatic int			/* Ascending order on nont */
Xgcmp(a,b)
XNTXTAB *a,*b;
X{
X    int i;
X
X    i=a->nont-b->nont;
X#ifdef TRACE
X    printf("gcmp: %s (%u) - %s (%u) = %u\n",namenont(a->nont),a->nont,
X	namenont(b->nont),b->nont,i);
X#endif
X    return i;
X}
X
END_OF_FILE
if test 1400 -ne `wc -c <'yagoto.c'`; then
    echo shar: \"'yagoto.c'\" unpacked with wrong size!
fi
# end of 'yagoto.c'
fi
if test -f 'yaincon.c' ; then
  echo shar: Will not clobber existing file \"'yaincon.c'\"
else
echo shar: Extracting \"'yaincon.c'\" \( 2675 characters \)
sed "s/^X//" >'yaincon.c' <<'END_OF_FILE'
X/* Yaincon.c	06-Nov-86	Read complete items of inconsistent states */
X/* 25-Jul-87 IBM */
X/* 30-Nov-88 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	rdincon()
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xvoid
Xrdincon()
X{
X    int v3,dposn,st,basest,ibase,i,n;
X
X    message("rdincon:");
X
X    trace(("rdincon: allocating irule size cnincon %u * sizeof(int) %u = %u\n",
X	cnincon,sizeof(int),cnincon*sizeof(int)));
X    irule=(int *)xalloc(cnincon*sizeof(int));
X    trace(("rdincon: allocating ist size cnincon %u * sizeof(int) %u = %u\n",
X	cnincon,sizeof(int),cnincon*sizeof(int)));
X    ist=(int *)xalloc(cnincon*sizeof(int));
X
X    fitem=xopen(nitem,"rb");
X
X    n=basest=ibase=i=0;		/* fitem file sorted by state number */
X    for (;;) {
X	trace(("rdincon: state=%u ibase=%u i=%u\n",basest,ibase,i));
X	st=getw(fitem);		/* Item state number */
X	if (st != basest) {
X
X/* 	consider situation at end :
X	- eof - incon table MUST be full hence will exit on i>=incon
X	      - must have inconsistent last state to get to eof, with
X		a complete item as last
X	- i>=cnincon
X	      - i can only be ++ on complete items so last table entry
X		will be a complete item
X	      - if it is a complete item of a simple (consistent) state
X		then the next state value will be different, the inconsistent
X		test will be applied and i set down to ibase to go around
X		again
X	      - if it is a complete item of an inconsistent state, it MUST
X		be the last complete item (else i<cnincon), hence we don't
X		want to go any further. We test for i>=incon here as well
X		so that trace will put out the inconsistent message for the
X		last complete item, even if it is followed by other items
X		of the same state (incomplete of course), because we will
X		break on i>=incon whether we have read the rest of the state
X		or not.
X	- hence it is never possible to allow looping with i>= cnincon
X	(which would lead to scrunging outside allocated bounds)
X*/
X	    if (i != ibase && n>1) {
X		ibase=i;
X		trace(("rdincon: inconsistent\n"));
X	    }
X	    else {
X		i=ibase;
X	    }
X	    if (i >= cnincon)
X		break;
X	    basest=st;
X	    n=0;
X	}
X
X	(void)getw(fitem);		/* Item lhs symbol - can get from v3 */
X	v3=getw(fitem);			/* Item rule */
X	dposn=getw(fitem);		/* Item distinguished posn */
X	trace(("rdincon: %u: st=%u lhs=%s rule=%u dposn=%u\n",
X		i,st,namesym(rulesym[v3]),v3,dposn));
X	++n;				/* Count items in THIS state */
X	if (dposn == 0) {
X	    ist[i]=st;
X	    irule[i]=v3;
X	    ++i;			/* Record complete items only */
X	}
X    }
X    xclose(fitem,nitem);
X}
X
END_OF_FILE
if test 2675 -ne `wc -c <'yaincon.c'`; then
    echo shar: \"'yaincon.c'\" unpacked with wrong size!
fi
# end of 'yaincon.c'
fi
if test -f 'yainit1.c' ; then
  echo shar: Will not clobber existing file \"'yainit1.c'\"
else
echo shar: Extracting \"'yainit1.c'\" \( 5994 characters \)
sed "s/^X//" >'yainit1.c' <<'END_OF_FILE'
X/* Yainit1.c	15-Jan-87 */
X/* 20-Jul-87 IBM */
X/* 25-Mar-88 VAXVMS */
X/* 08-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	init1()		fini1()
X
X	Statics:	ecopy()		argparse()	maketname()
X			makesname()
X
X	Uses:		ithash()	opsym()		ophead()
X			fnhash()	nxtchar()	flinenum()
X*/
X
X#include <stdio.h>
X
X#define PHASE1
X
X#include "yadefs.h"
X
Xvoid
Xinit1(argc,argv)
Xint argc;
Xchar *argv[];
X{
X    void argparse(),maketname(),makesname(),ithash();
X
X    /* no message("init1:") because -g option not set yet */
X
X    argparse(argc,argv);
X
X    message("init1:");
X
X    maketname();
X    makesname();
X
X    if (o_inname) {
X	finput=xopen(o_inname,"r");
X    }
X    else {
X	finput=stdin;
X    }
X    fytabc=xopen(nytabc,"w");		/* MUST be done before itlex() */
X					/* hence can't be opened by parser */
X					/* (lex lookahead may output to file)*/
X    fprintf(fytabc,"/* %s */\n\n",VERSION);
X    if (o_define) {			/* Because it may be used by */
X	fytabh=xopen(nytabh,"w");	/* yylex() & opsym() & ophead() */
X	fprintf(fytabh,"/* %s */\n\n",VERSION);
X    }
X
X
X    ithash();
X    cnwarning=cnfatal=0;
X}
X
Xvoid
Xfini1()
X{
X    void opsym(),ophead(),ecopy(),fnhash(),flinenum();
X
X    message("fini1:");
X
X    xclose(faction,naction);
X
X    opsym();		/* token defines BEFORE tail */
X    ophead();		/* miscellaneous defines */
X
X    flinenum(fytabc);
X    ecopy(fytabc);
X
X    xclose(fytabc,nytabc);
X
X    if (o_define) {
X	xclose(fytabh,nytabh);
X    }
X
X    if (o_inname) {
X	xclose(finput,o_inname);
X    }
X
X    fnhash();
X}
X
Xstatic void
Xecopy(f)
XFILE *f;
X{
X    void nxtchar();
X
X    while (ch != EOF) {
X	putc(ch,f);
X	nxtchar();
X    }
X}
X
Xstatic void
Xargparse(argc,argv)			/* Get command line args */
Xint argc;
Xchar *argv[];
X{
X    int err;
X    char *s;
X
X    o_listall=o_define=o_yydebug=o_verbose=o_debug=0;
X    o_linenum=1;
X    o_inname=NULL;
X    err=0;
X    while (--argc && !err) {		/* Ignore arg0 */
X	s= *++argv;			/* "= *" avoids old assignment op */
X	if (*s++ == '-') {
X	    while (*s) {
X		switch (toupper(*s++)) {
X		    case '-':	break;
X		    case 'D':	o_define=1; break;
X		    case 'L':	o_linenum=0; break;
X		    case 'T':	o_yydebug=1; break;
X		    case 'V':	o_verbose=1; break;
X		    case 'A':	o_listall=1; break;
X		    case 'G':	o_debug=1; break;
X		    case 'H':	/* fall thru for help */
X		    default:	err=1;
X		}
X	    }
X	}
X	else {
X	    if (o_inname) {
X		err=1;
X	    }
X	    else {
X		o_inname= *argv;
X	    }
X	}
X    }
X    if (err) {
X	fprintf(stderr,"%s %s\n(%s code,%s data,%u bit strings)\n\n",
X		VERSION,SYSTEM,CODEMODEL,DATAMODEL,BITLNG);
X	fprintf(stderr,"Usage:  %syacc -dvatlgh [file]\n",PREAMBLE);
X	fprintf(stderr,"Where:  -d send definition to %s\n",nytabh);
X	fprintf(stderr,"        -v send parser,conflicts & statistics to %s\n",
X					noutput);
X	fprintf(stderr,"        -a list ALL conflicts, even if resolved\n");
X	fprintf(stderr,"        -t debugging is activated by default\n");
X	fprintf(stderr,"        -l do not output #line constructs\n");
X	fprintf(stderr,"        -g describe yacc's progress on stdout\n");
X	fprintf(stderr,"        -h help - this message\n");
X	fprintf(stderr,"Input:  comes from stdin (which may be redirected)\n");
X	fprintf(stderr,"        or file if explicitly specified\n");
X	fprintf(stderr,"Output: goes to %s\n",nytabc);
X	fprintf(stderr,"Errors: go to stderr, as do conflicts unless -v\n");
X	exit(1);
X    }
X}
X
Xvoid
Xmaketname()		/* make names for temporary files */
X{
X    char *tmppath;
X    unsigned lenv;
X
X#ifdef SKELENVPATH
X    if ((tmppath=getenv(TMPENVPATH)) == NULL) {
X#else
X    {
X#endif
X	tmppath=strcpy(malloc(strlen(TMPDEFPATH)+1),TMPDEFPATH);
X    }
X    if (strlen(tmppath)) {	/* don't add slash unless path exists */
X	strcat(
X	    strcpy((g_tmppath=malloc(strlen(tmppath)+2)),tmppath)
X	    ,PATHSEPARATOR);
X	free(tmppath);
X    }
X    else {
X	g_tmppath=tmppath;
X    }
X    lenv=strlen(g_tmppath);
X
X    strcat(
X	strcpy(
X	    (naction=malloc(lenv+strlen(tnaction)+1))
X	     ,g_tmppath)
X	,tnaction);
X    strcat(
X	strcpy(
X	    (nstring=malloc(lenv+strlen(tnstring)+1))
X	     ,g_tmppath)
X	,tnstring);
X    strcat(
X	strcpy(
X	    (nsymbol=malloc(lenv+strlen(tnsymbol)+1))
X	     ,g_tmppath)
X	,tnsymbol);
X    strcat(
X	strcpy(
X	    (nrule=malloc(lenv+strlen(tnrule)+1))
X	     ,g_tmppath)
X	,tnrule);
X    strcat(
X	strcpy(
X	    (nrhs=malloc(lenv+strlen(tnrhs)+1))
X	     ,g_tmppath)
X	,tnrhs);
X    strcat(
X	strcpy(
X	    (nitem=malloc(lenv+strlen(tnitem)+1))
X	     ,g_tmppath)
X	,tnitem);
X    strcat(
X	strcpy(
X	    (ngoto=malloc(lenv+strlen(tngoto)+1))
X	     ,g_tmppath)
X	,tngoto);
X    strcat(
X	strcpy(
X	    (nshift=malloc(lenv+strlen(tnshift)+1))
X	     ,g_tmppath)
X	,tnshift);
X    strcat(
X	strcpy(
X	    (ntr2=malloc(lenv+strlen(tntr2)+1))
X	     ,g_tmppath)
X	,tntr2);
X    strcat(
X	strcpy(
X	    (ntrans=malloc(lenv+strlen(tntrans)+1))
X	     ,g_tmppath)
X	,tntrans);
X
X#ifdef TRACE
X    printf("maketname: %s\n",naction);
X    printf("maketname: %s\n",nstring);
X    printf("maketname: %s\n",nsymbol);
X    printf("maketname: %s\n",nrule);
X    printf("maketname: %s\n",nrhs);
X    printf("maketname: %s\n",nitem);
X    printf("maketname: %s\n",ngoto);
X    printf("maketname: %s\n",nshift);
X    printf("maketname: %s\n",ntr2);
X    printf("maketname: %s\n",ntrans);
X#endif
X}
X
Xvoid
Xmakesname()		/* make name for parser skeleton file */
X{
X    char *skelpath,*workpath;
X    unsigned lenv;
X
X#ifdef SKELENVPATH
X    if ((workpath=getenv(SKELENVPATH)) == NULL) {
X#else
X    {
X#endif
X	workpath=strcpy(malloc(strlen(SKELDEFPATH)+1),SKELDEFPATH);
X    }
X    if (strlen(workpath)) {	/* don't add slash unless path exists */
X	strcat(
X	    strcpy((skelpath=malloc(strlen(workpath)+2)),workpath)
X	    ,PATHSEPARATOR);
X	free(workpath);
X    }
X    else {
X	skelpath=workpath;
X    }
X    lenv=strlen(skelpath);
X
X    strcat(
X	strcpy(
X	    (nyaccpar=malloc(lenv+strlen(SKELDEFNAME)+1))
X	     ,skelpath)
X	,SKELDEFNAME);
X
X#ifdef TRACE
X    printf("makesname: %s\n",nyaccpar);
X    exit(1);
X#endif
X}
X
END_OF_FILE
if test 5994 -ne `wc -c <'yainit1.c'`; then
    echo shar: \"'yainit1.c'\" unpacked with wrong size!
fi
# end of 'yainit1.c'
fi
if test -f 'yalex.c' ; then
  echo shar: Will not clobber existing file \"'yalex.c'\"
else
echo shar: Extracting \"'yalex.c'\" \( 13664 characters \)
sed "s/^X//" >'yalex.c' <<'END_OF_FILE'
X/* Yalex.c		Lexical analyzer */
X/* 25-Jul-87 IBM */
X/* 25-Mar-88 VAXVMS */
X/* 07-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	yalex()		nxtchar()	unchar()
X			where()		flinenum()
X
X	Statics:	clrbuf()	addbuf()	insbuf()
X			iscomment()	isstring()	iswhite()
X			skipwhite()	skipwst()	match()
X			acopy()		ucopy()		dcopy()
X			gettag()	puttag()	nxtcopy()
X
X	Uses:		chksym()	errmsg()	settok()
X*/
X
X#include <stdio.h>
X
X#include <ctype.h>
X
X#ifdef TTYHEAD
X#include TTYHEAD
X#endif
X
X#define	isodigit(x)	(x >= '0' && x <= '7')
X#define	isidstart(x)	(isalpha(x) || x == '_')
X#define	isidbody(x)	(isalnum(x) || x == '_')
X
X#define PHASE1
X
X#include "yadefs.h"
X
X#include "yalex.h"			/* Renamed ytab.h from parser */
X
XYYSTYPE yylval;				/* NB. Must be ancestor of yaparse.c */
X
Xstatic int linenum = 0;			/* Count of input line (starts at 1) */
Xstatic char lexbuf[BUFLNG];
Xstatic char *bufp,*bufend;
Xstatic char *tagname;			/* Union tag in actions */
X
Xint
Xyylex()
X{
X    int match();
X    void clrbuf(),addbuf(),insbuf(),skipwhite(),nxtchar();
X    void dcopy(),ucopy(),acopy();
X    void flinenum();
X    SYMBOL *chksym();
X    void settok();
X    void unchar();
X
X    register int i;
X    int t;
X    int delim;
X
X    if (linenum == 0) nxtchar();	/* First time through */
X
X    clrbuf();
X    skipwhite();
X
X    if (isdigit(ch)) {
X	do {
X    	    addbuf(ch);
X    	    nxtchar();
X	} while (isdigit(ch));
X	yylval.u_symbol=chksym(lexbuf);
X	return NUMBER;
X    }
X
X    if (isidstart(ch)) {			/* Identifier */
X	do {
X    	    addbuf(ch);
X    	    nxtchar();
X	} while (isidbody(ch));
X	skipwhite();				/* Lookahead for colon */
X	yylval.u_symbol=chksym(lexbuf);
X	if (ch == ':') {
X    	    return C_IDENTIFIER;
X	}
X	else {
X    	    return IDENTIFIER;
X	}
X    }
X
X    switch (ch) {
X	case '\"':
X	case '\'':
X			delim=ch;
X			nxtchar();			/* Character Const */
X			switch (ch) {
X			    case '\"':
X			    case '\'':
X					if (ch == delim) {
X					    i=0;	/* '' -> null */
X					}
X					else {		/* ordinary char */
X					    i=ch;
X					    addbuf(ch);
X					    nxtchar();
X					}
X					break;
X			    case '\\':	addbuf(ch);
X					nxtchar();	/* escape character */
X					if (isodigit(ch)) {
X					    i=0;
X					    while (isodigit(ch)) {
X						i=(i<<3) + (ch-'0');
X						addbuf(ch);
X						nxtchar();
X					    }
X					    i=i & 0377;
X					}
X					else {
X					    switch (ch) {
X						case 'n':  i='\n'; break;
X						case 't':  i='\t'; break;
X						case 'b':  i='\b'; break;
X						case 'r':  i='\r'; break;
X						case 'f':  i='\f'; break;
X						case '\\': i='\\'; break;
X						case '\'': i='\''; break;
X						case '\"': i='\"'; break;
X						default:   i=ch;
X					    }
X					    addbuf(ch);
X					    nxtchar();
X					}
X					break;
X			    default:	i=ch;		/* ordinary char */
X					addbuf(ch);
X					nxtchar();
X			}
X			t=LITERAL;
X			while (ch != delim && ch != EOF) {
X			    t=IDENTIFIER;	/* if > 1 character */
X			    addbuf(ch);
X			    nxtchar();
X			}
X			if (ch != EOF) {	/* trailing quote */
X			    nxtchar();
X			}
X			if (t == IDENTIFIER) {
X			    skipwhite();
X			    if (ch == ':') {
X				t=C_IDENTIFIER;
X			    }
X			}
X			else {			/* LITERAL - reinsert quotes */
X			    addbuf('\'');
X			    insbuf('\'');
X			}
X			yylval.u_symbol=chksym(lexbuf);
X			if (t == LITERAL) {
X			    settok(yylval.u_symbol,i);
X			    /* token number is char value */
X			}
X			return t;
X
X	case '=':	nxtchar();
X			if (ch != '{') {
X			    unchar();
X			    ch='=';
X			}
X			/* fall thru */
X	case '{':	delim=(ch == '=') ? ';' : '}';
X			if (section == RULES) {
X			    fprintf(faction,"\ncase %d: {\n",nextrule);
X			    flinenum(faction);
X			    nxtchar();
X			    acopy(faction,delim);
X			    if (delim == ';') fputs(";",faction);
X			    fputs("\n} break;\n",faction);
X    			    return ACTBODY;
X    			}
X			else {				/* assume definition */
X			    ucopy();
X			    return UNIONBODY;
X			}
X
X	case '\\':
X	case '%':	nxtchar();
X	    		switch (ch) {
X			    case '\\':
X    			    case '%':	nxtchar();
X					if (section == RULES) {
X					    return 0;	/* End marker */
X					}
X					else {
X					    return MARK;
X					}
X   	 		    case '{':	flinenum(fytabc);
X					nxtchar();
X					dcopy(fytabc);
X    					return DEFBODY;
X    			    case '<':	nxtchar(); return YLEFT;
X    			    case '>':	nxtchar(); return YRIGHT;
X    			    case '2':	nxtchar(); return YNONASSOC;
X    			    case '0':	nxtchar(); return YTOKEN;
X    			    case '=':	nxtchar(); return YPREC;
X    			    case 'l':	if (match("left")) {
X    					    return YLEFT;
X    					}
X    					break;
X    			    case 'r':	if (match("right")) {
X    					    return YRIGHT;
X    					}
X    					break;
X    			    case 'n':	if (match("nonassoc")) {
X    					    return YNONASSOC;
X    					}
X    					break;
X    			    case 'b':	if (match("binary")) {
X    					    return YNONASSOC;
X    					}
X    					break;
X    			    case 't':	if (match("token")) {
X    					    return YTOKEN;
X    					}
X    					else if (match("erm")) {
X    					    return YTOKEN;
X    					}
X    					else if (match("ype")) {
X    					    return YTYPE;
X    					}
X    					break;
X    			    case 'p':	if (match("prec")) {
X    					    return YPREC;
X    					}
X    					break;
X    			    case 's':	if (match("start")) {
X    					    return YSTART;
X    					}
X    					break;
X    			    case 'u':	if (match("union")) {
X    					    return YUNION;
X    					}
X    					break;
X    			}
X			errmsg("Invalid %command",FATAL);
X			return BADCHAR;
X
X	case	':':	nxtchar(); return COLON;
X	case	';':	nxtchar(); return SEMICOLON;
X	case	',':	nxtchar(); return COMMA;
X	case	'<':	nxtchar(); return LANGLE;
X	case	'>':	nxtchar(); return RANGLE;
X	case	'|':	nxtchar(); return BAR;
X    }
X    if (ch == EOF) {
X	return 0;
X    }
X    else {
X	nxtchar();
X	return BADCHAR;
X    }
X}
X
Xstatic void
Xclrbuf()
X{
X    bufp=lexbuf;				/* first char in lexbuf */
X    *bufp='\0';
X    bufend=lexbuf+BUFLNG-1;			/* last char in lexbuf */
X}
X
Xstatic void
Xaddbuf(i)
Xregister int i;
X{
X    void errmsg();
X
X    if (bufp < bufend) {			/* ensures space for \0 */
X	*bufp=i;
X	*++bufp='\0';
X    }
X    else
X	errmsg("Lex buffer ovf",ABORT);
X}
X
Xstatic void
Xinsbuf(i)
Xint i;
X{
X    void errmsg();
X    register char *p;
X
X    if (bufp < bufend) {
X	for (p= ++bufp; p > lexbuf; p--) {
X	    *p= *(p-1);		/* "= *" and "= ++" avoid old assignment ops */
X	}
X	*p=i;
X    }
X    else
X	errmsg("Lex buffer ovf",ABORT);
X}
X
Xstatic int				/* Does current ch start a string ? */
Xisstring(f1,f2)				/* If so copy to f1,f2 & get next ch */
XFILE *f1,*f2;
X{
X    void nxtcopy();
X    int quote;
X
X    if (ch == '\'' || ch == '\"') {
X	quote=ch;
X	do {
X	    nxtcopy(f1,f2);
X	    if (ch == '\\') {			/* Avoid escaped quotes */
X		nxtcopy(f1,f2);			/* Ignore escape character */
X		nxtcopy(f1,f2);			/* and its successor */
X	    }
X	} while (ch != quote && ch != EOF);
X	if (ch == quote) nxtcopy(f1,f2);
X	return 1;
X    }
X    else {
X	return 0;
X    }
X}
X    
Xstatic int				/* Does current ch start a comment ? */
Xiscomment(f1,f2)			/* If so copy to f1,f2 & get next ch */
XFILE *f1,*f2;
X{
X    void unchar(),nxtcopy(),nxtchar();
X
X    if (ch == '/') {
X	nxtchar();
X	if (ch == '*') {
X	    if (f1) putc('/',f1);
X	    if (f2) putc('/',f2);
X	    do {
X		nxtcopy(f1,f2);
X		if (ch == '*') {
X		    nxtcopy(f1,f2);
X		    if (ch == '/') {
X			nxtcopy(f1,f2);
X			return 1;	/* Leaves next char past / in ch */
X		    }
X		}
X	    } while (ch != EOF);
X	    return 1;			/* Comment terminated by EOF !! */
X	}
X	else {
X	    unchar();
X	    ch='/';
X	}
X    }
X    return 0;
X}
X    
Xstatic int				/* Is current ch whitespace ? */
Xiswhite(f1,f2)				/* If so copy to f1,f2 & get next ch */
XFILE *f1;
XFILE *f2;
X{
X    void nxtcopy();
X
X    if (isspace(ch)) {
X	nxtcopy(f1,f2);
X	return 1;
X    }
X    else {
X	return 0;
X    }
X}
X
Xstatic void				/* Skip whitespace & comments */
Xskipwhite()
X{
X    int iswhite(),iscomment();
X
X    while (iswhite(NULL,NULL) || iscomment(NULL,NULL)) {
X    }
X}
X
Xstatic void				/* Skip whitespace,comments, strings */
Xskipwst(f1,f2)				/* (copying skipped chars to f1 & f2)*/
XFILE *f1,*f2;
X{
X    int iswhite(),iscomment(),isstring();
X
X    while (iswhite(f1,f2) || iscomment(f1,f2) || isstring(f1,f2)) {
X    }
X}
X
Xstatic int
Xmatch(s)
Xregister char *s;
X{
X    void nxtchar();
X
X    while (ch == *s) {
X	++s;
X	nxtchar();
X    }
X    return (*s == 0);			/* Matched until end of string */
X}
X
Xstatic void				/* Output current character */
Xnxtcopy(f1,f2)				/* and then get the next one */
XFILE *f1;
XFILE *f2;
X{
X    void nxtchar();
X
X    if (f1) putc(ch,f1);
X    if (f2) putc(ch,f2);
X    nxtchar();
X}
X
Xvoid
Xnxtchar()
X{
X    if (linenum == 0 || ch == '\n') {	/* Won't look at nonexistent */
X					/* ch first time through */
X	++linenum;
X	if (isatty(fileno(finput))) {
X	    fputs(PROMPT,stderr);
X	}
X    }
X    ch=getc(finput);
X    if (iseofchar(ch)) {	/* defined in yasystem.h */
X	ch=EOF;
X    }
X}
X
Xvoid
Xwhere(f)				/* Display input location */
XFILE *f;
X{
X    fprintf(f,"[At line %d]",linenum);
X}
X
Xvoid
Xunchar()
X{
X    ungetc(ch,finput);
X}
X
Xvoid
Xflinenum(f)				/* Write input linenum to output */
XFILE *f;
X{
X    if (o_linenum)
X	fprintf(f,"\n#line %d\n",linenum);  /* NB. MUST be at start of line */
X}
X
Xstatic void
Xacopy(f,end)			/* Copy until '}' or ';', replacing "$nn" */
XFILE *f;			/* Doesn't detect either in comments */
Xint end;			/* either '}' or ';' (NOT copied) */
X{
X    void puttag(),gettag(),skipwst(),nxtchar();
X    int i,depth;
X
X    depth=0;
X    while (ch != EOF) {
X	skipwst(f,NULL);
X	switch (ch) {
X		case ';':	nxtchar();
X				if (end == ';') {
X				    return;
X				}
X				putc(';',f);
X				break;
X		case '{':	++depth;
X				putc('{',f);
X				nxtchar();
X				break;
X		case '}':	nxtchar();
X				if (depth-- == 0 && end == '}') {
X				    return;
X				}
X				putc('}',f);
X				break;
X		case '$':	nxtchar();
X				gettag();
X				if (ch == '$') {
X				    fputs("yyval",f);
X				    puttag(f,1,0);
X				    nxtchar();
X				}
X				else {
X				    if (isdigit(ch) || ch == '-') {
X					clrbuf();
X					if (ch == '-') {
X					    addbuf(ch);
X					    nxtchar();
X					    if (!isdigit(ch)) {
X						errmsg("$- but no number",
X							FATAL);
X					    }
X					}
X					while (isdigit(ch)) {
X					    addbuf(ch);
X					    nxtchar();
X					}
X					i=atoi(lexbuf);
X					if (i > g_offset) {
X					    errmsg("$nn is too far right",
X						FATAL);
X					}
X					fprintf(f,"yypvt[%d]",i-g_offset);
X					puttag(f,0,i);
X				    }
X				    else {
X					errmsg("$ not followed by $ or number",
X						FATAL);
X				    }
X				}
X				break;
X		default:	putc(ch,f);
X				nxtchar();
X				break;
X	}
X    }
X}
X
Xstatic void
Xucopy()				/* Copy until "}" except in comment */
X{
X    void skipwst(),nxtchar();
X
X    fputs("\ntypedef union {\n",fytabc);
X    flinenum(fytabc);
X    if (o_define) {
X	fputs("\ntypedef union {\n",fytabh);
X	flinenum(fytabh);
X    }
X    else {
X	fytabh=0;		/* For skipwst's benefit */
X    }
X    nxtchar();
X    for (;;) {
X	skipwst(fytabc,fytabh);
X	if (ch == '}' || ch == EOF) {
X	    break;
X	}
X	putc(ch,fytabc);
X	if (o_define) putc(ch,fytabh);
X	nxtchar();
X    }
X    nxtchar();			/* absorb trailing } */
X
X    fputs("} YYSTYPE;\n",fytabc);
X    if (o_define) fputs("} YYSTYPE;\n",fytabh);
X}
X
Xstatic void
Xdcopy(f)			/* Copy until "%}" except in comment */
XFILE *f;
X{
X    void skipwst(),nxtchar();
X
X    for (;;) {
X	skipwst(f,NULL);
X	if (ch == EOF) {
X	    break;
X	}
X	if (ch == '%' || ch == '\\') {
X	    int delim=ch;
X	    nxtchar();
X	    if (ch == '}') {
X		nxtchar();
X		break;
X	    }
X	    else {
X		unchar();
X		ch=delim;
X	    }
X	}
X	putc(ch,f);
X	nxtchar();
X    }
X}
X
Xvoid
Xgettag()			/* Read union tag xxx from $<xxx>nn */
X{
X    if (ch == '<') {
X 	clrbuf();
X	nxtchar();
X	while (ch != '>') {
X	    addbuf(ch);
X	    nxtchar();
X	}
X	nxtchar();		/* Absorb trailing > */
X	tagname=xalloc(strlen(lexbuf)+1);
X	strcpy(tagname,lexbuf);
X    }
X    else {
X	tagname=NULL;
X    }
X}
X
Xvoid
Xputtag(f,lflag,nn)		/* Put optional union tag into output stream */
XFILE *f;
Xint lflag;			/* 0 = right symbol ($nn), 1 = left ($$) */
Xint nn;				/* $nn if right symbol */
X{
X    char *tag;
X    LIST *list;
X
X    if (g_typeon) {
X	trace(("puttag: type checking is on\n"));
X	if (lflag) {
X	    trace(("puttag: lflag\n"));
X	    if (tagname) {		/* Explicitly specified type */
X		tag=tagname;		/* used for embedded actions */
X	    }
X	    else {			/* Type of left non-terminal */
X		tag=g_cid->type;	/* used for trailing actions */
X		if (tag == 0) {
X		    errmsg("$$ has no type",FATAL);
X		}
X	    }
X	    /* NB. Don't know whether or embedded or trailing action yet
X	       because we can't lookahead that far, but we need to emit
X	       a tag now. Check the appropriateness of the selection
X	       after the action.
X	    */
X	}
X	else {
X	    if (nn >= 1) {	/* Find symbol in current rule */
X		trace(("puttag: checking rule %04x for nn %d\n",g_rule,nn));
X		for (list=g_rule->list; nn > 1 && list; --nn,list=list->next);
X		if (list) {
X		    tag=list->sym->type;
X		    if (tag) {
X			if (tagname) {
X			    if (strcmp(tag,tagname) == 0) {
X				errmsg("Explicit type unnecessary",WARNING);
X			    }
X			    else {
X				errmsg("Explicit type different from symbol",
X				    FATAL);
X			    }
X			}
X		    }
X		    else {
X			if (tagname) {
X			    tag=tagname;
X			}
X			else {
X			    errmsg("Right-hand symbol has no type",FATAL);
X			}
X		    }
X		}
X		else {
X		    /* right context reference illegal - checked already */
X		    tag=0;
X		}
X	    }
X	    else {
X		if (tagname) {
X		    tag=tagname;
X		}
X		else {
X		    errmsg("Left context reference requires explicit type",
X			FATAL);
X		    tag=0;
X		}
X	    }
X	}
X
X	if (tag) {
X	    trace(("puttag: tag is <%s>\n",tag));
X	    fprintf(f,".%s",tag);
X	}
X    }
X    else {			/* Type checking not turned on */
X	if (tagname) {		/* But explicit type was specified */
X	    errmsg("Type checking is not activated",FATAL);
X	}
X    }
X}
X
END_OF_FILE
if test 13664 -ne `wc -c <'yalex.c'`; then
    echo shar: \"'yalex.c'\" unpacked with wrong size!
fi
# end of 'yalex.c'
fi
if test -f 'yalex.h' ; then
  echo shar: Will not clobber existing file \"'yalex.h'\"
else
echo shar: Extracting \"'yalex.h'\" \( 600 characters \)
sed "s/^X//" >'yalex.h' <<'END_OF_FILE'
X/* yacc version 0.05 July 9, 1989 1:53 AM */
X
X
Xtypedef union {
X
X#line 27
X
X	int	u_int;
X	RULE	*u_rule;
X	SYMBOL	*u_symbol;
X} YYSTYPE;
X#define error	256
X#define BADCHAR	257
X#define LITERAL	258
X#define IDENTIFIER	259
X#define C_IDENTIFIER	260
X#define NUMBER	261
X#define YLEFT	262
X#define YRIGHT	263
X#define YNONASSOC	264
X#define YTOKEN	265
X#define YPREC	266
X#define YTYPE	267
X#define YSTART	268
X#define YUNION	269
X#define MARK	270
X#define ACTBODY	271
X#define DEFBODY	272
X#define UNIONBODY	273
X#define COMMA	274
X#define COLON	275
X#define SEMICOLON	276
X#define BAR	277
X#define LANGLE	278
X#define RANGLE	279
X
END_OF_FILE
if test 600 -ne `wc -c <'yalex.h'`; then
    echo shar: \"'yalex.h'\" unpacked with wrong size!
fi
# end of 'yalex.h'
fi
if test -f 'yalook.c' ; then
  echo shar: Will not clobber existing file \"'yalook.c'\"
else
echo shar: Extracting \"'yalook.c'\" \( 5223 characters \)
sed "s/^X//" >'yalook.c' <<'END_OF_FILE'
X/* Yalook.c	06-Nov-86	Compute lookahead sets */
X/* 25-Mar-88 VAXVMS */
X/* 09-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	lookahead()	dialloc()	difree()
X			diclear()	fwreln()	rereln()
X			recopy()	reunion()
X
X	Statics:	traverse()	[dpila(),dpwork() - TRACE]
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xstatic int *stkend;			/* End of stack */
X
Xvoid
Xlookahead()
X{
X    void dialloc(),difree(),diclear(),traverse();
X    void dpwork(),dpila();
X    void recopy(),reunion();
X    int rereln(),fwreln();
X    int spells();
X    int i,ntx;
X
X    message("lookahead:");
X
X    dmax=cnntx;
X    dialloc();
X    diclear();
X
X    dicopy=recopy;
X    diunion=reunion;
X    direln=rereln;		/* Relation is reads */
X
X    for (ntx=0; ntx<cnntx; ++ntx) {
X	traverse(ntx);
X    }
X#ifdef TRACE
X    dpwork("Read");
X#endif
X    diclear();
X    direln=fwreln;
X
X    ila=(BITSTR **)xalloc(cnincon*sizeof(BITSTR *));
X
X    for (i=0; i<cnincon; ++i) {
X	ila[i]=alcbit(cntok);
X	zerobit(ila[i],cntok);
X	for (ntx=0; ntx<cnntx; ++ntx) {
X	    if (isbit(lback[i],ntx)) {
X		trace(("lookahead: ntx %u in lookback item %u\n",ntx,i));
X		traverse(ntx);
X		if (work[ntx]) {
X		    trace(("lookahead: work allocated\n"));
X		    orbit(ila[i],work[ntx],cntok);
X		}
X		else {
X		    trace(("lookahead: no work - or with dread\n"));
X		    orbit(ila[i],dread[ntxtab[ntx].to],cntok);
X		}
X	    }
X	}
X    }
X#ifdef TRACE
X    dpwork("Follow");
X    dpila();
X#endif
X    difree();
X}
X
Xvoid
Xtraverse(x)
Xint x;
X{
X    int d,y;
X
X    trace(("traverse: enter %u\n",x));
X
X    if (din[x]) {
X	trace(("traverse: already done\n"));
X	return;
X    }
X
X/*    *++sp=x; */
X
X    if (sp < stkend) {
X	*++sp=x;
X    }
X    else {
X	bug("traverse: stack overflow");
X    }
X    din[x]=d= ++depth;			/* Record depth (which may change) */
X					/* "= ++" avoids old assignment op */
X#ifdef TRACE
X    printf("traverse: din=");
X    for (y=0; y<dmax; ++y) printf("%u ",din[y]);
X    printf("\n");
X#endif
X    for (y=0; y<dmax; ++y) {
X	if ( (*direln)(x,y) ) {
X	    trace(("traverse: %u reln %u\n",x,y));
X	    if (din[y] == 0) {
X		trace(("traverse: recursive call for %u\n",y));
X		traverse(y);
X	    }
X	    trace(("traverse: Nx=%u Ny=%u\n",din[x],din[y]));
X	    if (din[x] > din[y]) {	/* Nx = min (Nx,Ny) */
X		trace(("traverse: so set x to min\n"));
X		din[x]=din[y];
X	    }
X	    (*diunion)(x,y);
X	}
X    }
X    if (din[x] == d) {			/* NOT depth or will never do it ! */
X	trace(("traverse: = original depth\n"));
X	do {
X	    trace(("traverse: popping %u\n",*sp));
X	    din[*sp]=INFINITY;
X	    if (*sp != x) {
X		(*dicopy)(*sp,x);
X	    }
X	} while (--depth, *sp-- != x);	/* pop(top of stack) != x */
X    }
X    trace(("traverse: exit %u\n",x));
X}
X
X#ifdef TRACE
Xstatic void
Xdpila()
X{
X    int i,j;
X
X    for (j=0; j<cnincon; ++j) {
X	printf("item %u reduce to %s on lookahead = ",
X	    j,namesym(rulesym[irule[j]]));
X	if (ila[j]) {
X	    for (i=0; i<cntok; ++i) {
X		if (isbit(ila[j],i)) {
X		    printf("%s ",nametok(i));
X		}
X	    }
X	    printf("\n");
X	}
X	else {
X	    printf("not allocated\n");
X	}
X    }
X}
X
Xstatic void
Xdpwork(desc)
Xchar *desc;
X{
X    int i,ntx;
X
X    for (ntx=0; ntx<cnntx; ++ntx) {
X	printf("%u(%u->%u on %s)\t%s = ",
X		ntx,ntxtab[ntx].from,ntxtab[ntx].to,
X		namenont(ntxtab[ntx].nont),desc);
X	if (work[ntx]) {
X	    for (i=0; i<cntok; ++i) {
X		if (isbit(work[ntx],i)) {
X		    printf("%s ",nametok(i));
X		}
X	    }
X	    printf("\n");
X	}
X	else {
X	    printf("not allocated\n");
X	}
X    }
X}
X#endif
X
Xvoid
Xdialloc()
X{
X    int i;
X
X    work=(BITSTR **)xalloc(dmax*sizeof(BITSTR *));
X    din=(int *)xalloc(dmax*sizeof(int));
X    stack=(int *)xalloc(DISTACKSIZE);
X    stkend=stack+DISTACKSIZE-1;	/* Points to last entry */
X
X    for (i=0; i<dmax; ++i){
X	work[i]=0;		/* Work bit strings initially empty */
X    }
X}
X
Xvoid
Xdifree()
X{
X    int i;
X
X    for (i=0; i<dmax; ++i){
X	if (work[i]) {
X	    xfree((char *)work[i]);
X	}
X    }
X    xfree((char *)work);
X    xfree((char *)din);
X    xfree((char *)stack);
X}
X
Xvoid
Xdiclear()
X{
X    int i;
X
X    for (i=0; i<dmax; ++i) {
X	din[i]=0;		/* Array used by traverse */
X    }
X
X    sp=stack-1;
X    depth=0;
X}
X
Xint
Xfwreln(ntx,nty)				/* Relation: ntx includes nty */
Xint ntx,nty;
X{
X    return isbit(incl[ntx],nty);
X}
X
Xint
Xrereln(ntx,nty)			/* Reads relation between nonterminal tx */
Xint ntx,nty;
X{
X    return (isbit(nullable,ntxtab[nty].nont)
X	    && ntxtab[ntx].to == ntxtab[nty].from);
X}
X
Xvoid
Xrecopy(ntx,nty)			/* x = y */
Xint ntx,nty;
X{
X    trace(("recopy: %u from %u\n",ntx,nty));
X
X    if (work[nty]) {
X	if (work[ntx]) {
X	    copybit(work[ntx],work[nty],cntok);
X	}
X	else {
X	    bug("recopy: destination not assigned");
X	}
X    }
X    else {
X	if (work[ntx]) {
X	    bug("recopy: source not assigned");
X	}
X    }
X}
X
Xvoid
Xreunion(ntx,nty)		/* x = x U y */
Xint ntx,nty;
X{
X    trace(("reunion: %u from %u\n",ntx,nty));
X
X    if (!work[ntx]) {
X	trace(("reunion: allocate %u to dread\n",ntx));
X	work[ntx]=alcbit(cntok);
X	copybit(work[ntx],dread[ntxtab[ntx].to],cntok);
X    }
X
X    if (work[nty]) {
X	orbit(work[ntx],work[nty],cntok);
X    }
X    else {
X	trace(("reunion: union with dread %u\n",nty));
X	orbit(work[ntx],dread[ntxtab[nty].to],cntok);
X    }
X}
X
END_OF_FILE
if test 5223 -ne `wc -c <'yalook.c'`; then
    echo shar: \"'yalook.c'\" unpacked with wrong size!
fi
# end of 'yalook.c'
fi
if test -f 'yalr0.c' ; then
  echo shar: Will not clobber existing file \"'yalr0.c'\"
else
echo shar: Extracting \"'yalr0.c'\" \( 11591 characters \)
sed "s/^X//" >'yalr0.c' <<'END_OF_FILE'
X/* Yalr0.c	20-Oct-86	Compute lr(0) sets of items */
X/* 30-Oct-86 	States are numbered from 0 not 1 */
X/* 05-Nov-86	Arrange addition of states to keep sorted by state number */
X/* 12-Nov-86	Optx() - outputs rules/dposn as well */
X/* 20-Nov-86	Optx() - add -1 as eof indicator */
X/* 27-Nov-86	count complex states and items */
X/* 17-Jan-87	Output null items (complete but in closure) as well as kernel*/
X/* 25-Jul-87 IBM */
X/* 25-Mar-88 VAXVMS */
X/* 09-Jul-89 ZTC*/
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X#define	PTRFMT	"%08lx"
X
X#ifdef	TRACE2				/* Strip off outer parentheses */
X#define	trace2(x)	printf x
X#else
X#define	trace2(x)
X#endif	/* TRACE2 */
X
X/*	Defines:	lr0()
X
X	Statics:	gentrans()	mrgtrans()	genclosure()
X			addtrans()	addstate()	additem()
X			freeitlist()	itemcmp()	optx()
X			freestlist()	opstlist()	opstate()
X			[dpitem() - TRACE]
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xvoid
Xlr0()
X{
X    STATE *addstate();
X    ITEM *additem();
X    void gentrans();
X    void mrgtrans();
X    void opstlist();
X    void freestlist();
X
X    STATE *st,*stlist,*stlast;
X    TRANS *trlist;
X
X    message("lr0:");
X
X    cnstate=0;
X    cnrtx=cnntx=cnttx=0;
X    ftrans=xopen(ntrans,"wb");
X
X    stlast=NULL;				/* None added yet */
X
X    /* First state is  start : _ .... */
X
X    st=stlist=addstate(&stlast,
X	additem((ITEM **)NULL,nontrule[valnont(start)],1));
X	/* (ZTC 14-Nov-88: cast shuts up compiler without using prototypes) */
X    
X    do {
X	trace(("lr0: st=%u\n",st->num));
X	gentrans(&trlist,st);			/* Generate transitions */
X	mrgtrans(&stlist,&stlast,st,&trlist);	/* Merge trans with states */
X	st=st->next;
X    } while (st);				/* Until no states added */
X
X    putw(-1,ftrans);				/* Eof indicator */
X    xclose(ftrans,ntrans);
X    opstlist(stlist);
X    freestlist(stlist);
X}
X
Xstatic void
Xgentrans(atrlist,st)
XTRANS **atrlist;
XSTATE *st;
X{
X    void dpitem();
X    void genclosure();
X    TRANS *addtrans();
X    ITEM *it;
X    int sym;
X
X    trace(("gentrans: st=%u atrlist=%08lx\n",st->num,atrlist));
X    it=st->item;
X    *atrlist=NULL;
X    while (it) {
X	trace(("gentrans: item "));
X#ifdef TRACE
X	dpitem(it);
X#endif
X	if (!iscomplete(it)) {
X	    trace(("gentrans: is not complete\n"));
X	    /* sym=dsym(it); */
X	    sym=rhs[rulerhs[it->rule]+it->dposn-1];
X
X	    trace(("gentrans: trlist=%08lx\n",*atrlist));
X	    (void)addtrans(atrlist,sym,it->rule,it->dposn+1);
X	    trace(("gentrans: trlist=%08lx\n",*atrlist));
X	    if (isnont(sym)) {
X		trace(("gentrans: %s is nont so closure\n",namesym(sym)));
X		genclosure(atrlist,st,sym);
X	    }
X	    trace(("gentrans: trlist=%08lx\n",*atrlist));
X	}
X	it=it->next;
X    }
X    trace(("gentrans: leaving with trlist=%08lx\n",*atrlist));
X}
X
Xstatic void
Xmrgtrans(astlist,astlast,fromst,atrlist)
XSTATE **astlist,**astlast,*fromst;
XTRANS **atrlist;
X{
X    void optx();
X    void freeitlist();
X    STATE *st,*addstate();
X    TRANS *tr;
X    int itemcmp();
X
X    trace2(("mrgtrans: entering atrlist=%08lx trlist=%08lx\n",atrlist,*atrlist));
X
X    while (tr= *atrlist) {		/* "= *" avoids old assignment op */
X	trace2(("mrgtrans: transition on %s from state number %d\n",
X		namesym(tr->sym),fromst->num));
X#ifdef TRACE2
X	dpitem(tr->item);
X#endif
X	for (st= *astlist; st && !itemcmp(st->item,tr->item); st=st->next);
X					/* "= *" avoids old assignment op */
X	if (st) {			/* If we found a match */
X	    trace2(("mrgtrans: matching state is number %d\n",st->num));
X	    freeitlist(tr->item);
X	}
X	else {				/* Else need a new state */
X	    trace2(("mrgtrans: no matching state - get new one\n"));
X	    st=addstate(astlast,tr->item);
X	}
X	optx(tr->sym,fromst->num,st->num,st->item);
X	*atrlist=tr->next;		/* Next entry to test */
X	xfree((char *)tr);		/* And release storage */
X    }
X
X    trace2(("mrgtrans: leaving trlist=%08lx\n",*atrlist));
X}
X
Xstatic void
Xgenclosure(atrlist,st,sym)
XTRANS **atrlist;
XSTATE *st;
Xint sym;				/* Sym will only ever be a nont */
X{
X    ITEM *additem();
X    TRANS *addtrans();
X    int nont,n,r,x;
X
X    nont=valnont(sym);
X    trace(("genclosure: of %s\n",namenont(nont)));
X    for (n=0; n<cnnont; ++n) {		/* For all nonterminals, n */
X	if (isbit(first[nont],n)) {	/* If n is in nont's first list */
X	    trace(("genclosure: %s is in first list\n",namenont(n)));
X	    for (r=nontrule[n]; r<nontrule[n+1]; ++r) {	/* For all n's rules */
X		trace(("genclosure: adding rule %u\n",r));
X		if (rulerhs[r] < rulerhs[r+1]) {	/* That aren't empty */
X		    trace(("genclosure: not empty\n"));
X		    x=rhs[rulerhs[r]];	/* Add transition to n : x _ .... */
X		    (void)addtrans(atrlist,x,r,2);
X		}
X		else {			/* Record empty rule in closure */
X		    trace(("genclosure: empty - add to empty list\n"));
X		    (void)additem(&st->empty,r,0);
X		}
X	    }
X	}
X    }
X}
X
Xstatic TRANS *
Xaddtrans(atrlist,sym,rule,dposn)	/* Add transition to list */
XTRANS **atrlist;
Xint sym;				/* On which to make transition */
Xint rule;				/* Rule to go to */
Xint dposn;				/* And its distinguished position */
X{
X    ITEM *additem();
X    TRANS *tr;
X
X    trace(("addtrans: on %s to rule %u posn %u\n",namesym(sym),rule,dposn));
X    trace(("addtrans: atrlist=%08lx\n",atrlist));
X    if (atrlist) {			/* If list exists, search it */
X	tr= *atrlist;			/* "= *" avoids old assignment op */
X	while (tr && tr->sym != sym) {	/* For a transition on sym */
X	    tr=tr->next;
X	}
X    }
X    else {
X	tr=NULL;
X    }
X
X    if (!tr) {				/* If no list, or not in list */
X	tr=(TRANS *)xalloc(sizeof(TRANS));	/* Then we need a new one */
X	tr->item=NULL;
X	tr->sym=sym;
X	if (atrlist) {			/* If adding to a list */
X	    tr->next= *atrlist;		/* Will be NULL if list empty */
X					/* "= *" avoids old assignment op */
X	    *atrlist=tr;		/* Link new entry at head of list */
X	}
X	else {				/* Not adding to list */
X	    tr->next=NULL;
X	}
X    }
X
X    if (dposn > lngrule(rule)) {	/* Check if should be complete */
X	dposn=0;
X    }
X    trace(("addtrans: tr->item was %08lx\n",tr->item));
X    (void)additem(&tr->item,rule,dposn);	/* Add new item to trans */
X    trace(("addtrans: tr->item is now %08lx\n",tr->item));
X
X    return tr;
X}
X
Xstatic STATE *
Xaddstate(astlast,it)			/* Add state to list */
XSTATE **astlast;			/* Where in list to append/insert */
XITEM *it;
X{
X    STATE *st;
X
X    st=(STATE *)xalloc(sizeof(STATE));
X    st->item=it;
X    st->empty=NULL;			/* No empty (complete/closure) items */
X    st->num=cnstate++;
X    trace(("addstate: adding %u *astlast=%08lx\n",st->num,*astlast));
X    if (*astlast) {
X	st->next=(*astlast)->next;		/* Insert after *astlast */
X	(*astlast)->next=st;
X    }
X    else {
X	st->next=NULL;				/* Append to empty */
X    }
X    *astlast=st;				/* Advance ptr to last */
X    return st;
X}
X
Xstatic ITEM *
Xadditem(aitlist,rule,dposn)
XITEM **aitlist;
Xint rule,dposn;
X{
X    ITEM *it,*it1,*it2;
X
X    trace(("additem: add rule %u dposn %u\n",rule,dposn));
X    trace(("additem: aitlist=%08lx\n",aitlist));
X
X    it1=NULL;				/* Previous entry in list */
X    if (aitlist) {			/* If adding to an existing list */
X	it2= *aitlist;			/* "= *" avoids old assignment op */
X	trace(("additem: list exists %08lx\n",it2));
X    }
X    else {
X	it2=NULL;
X    }
X    while (it2 && rule > it2->rule) {	/* Find where in list to insert */
X	it1=it2;
X	it2=it2->next;
X    }
X    while (it2 && rule == it2->rule && dposn > it2->dposn) {
X	it1=it2;
X	it2=it2->next;
X    }
X    trace(("additem: it1=%08lx it2=%08lx\n",it1,it2));
X    if (it2 && rule == it2->rule && dposn == it2->dposn) {
X	it=it2;			/* Already exists */
X	trace(("additem: already exists\n"));
X    }
X    else {			/* Create new item */
X	it=(ITEM *)xalloc(sizeof(ITEM));
X	trace(("additem: creating %08lx\n",it));
X	it->rule=rule;
X	it->dposn=dposn;
X	it->next=it2;		/* Will be NULL at end of list, or no list */
X
X	if (it1) {		/* Insert in middle or end of list */
X	    it1->next=it;
X	    trace(("additem: in middle\n"));
X	}
X	else {			/* Insert at head of list */
X	    if (aitlist) {	/* List actually exists */
X		*aitlist=it;	/* So change head */
X		trace(("additem: is new head\n"));
X	    }
X	}
X    }
X    return it;			/* Return new entry */
X}
X
Xstatic void
Xfreeitlist(itlist)
XITEM *itlist;
X{
X    ITEM *it;
X
X    while (it=itlist) {
X	trace(("freeitlist: freeing "));
X#ifdef TRACE
X	dpitem(it);
X#endif /* TRACE */
X	itlist=it->next;
X	xfree((char *)it);
X    }
X}
X
Xstatic int
Xitemcmp(it1,it2)		/* Compare two sorted item lists */
XITEM *it1,*it2;
X{
X    while (it1 && it2) {
X	if (it1->rule != it2->rule || it1->dposn != it2->dposn) {
X	    return 0;
X	}
X	it1=it1->next;
X	it2=it2->next;
X    }
X    if (it1 == it2) {		/* ie. both zero */
X	return 1;
X    }
X    else {			/* Else not same length therefore not same */
X	return 0;
X    }
X}
X
Xstatic void
Xoptx(sym,fromst,tost,it)	/* Output transition from state to state */
Xint sym;			/* On this symbol */
Xint fromst;
Xint tost;
XITEM *it;			/* Items in to state */
X{
X    int rule,dposn;
X
X    if (isnont(sym))
X	++cnntx;
X    else
X	++cnttx;
X
X    for (; it; it=it->next) {	/* For all items */
X	rule=it->rule;
X	dposn = it->dposn ? it->dposn-1 : lngrule(rule);
X	if (rhs[rulerhs[rule]+dposn-1] == sym) {	/* If tx FROM sym */
X	    ++cnrtx;
X	    putw(sym,ftrans); putw(fromst,ftrans); putw(tost,ftrans);
X	    putw(rule,ftrans); putw(dposn,ftrans);
X	    trace2(("optx: transition on %s from %u (rule %u dposn %u) to %u\n",
X		namesym(sym),fromst,rule,dposn,tost));
X	}
X    }
X}
X
Xstatic void
Xfreestlist(stlist)
XSTATE *stlist;
X{
X    STATE *st;
X
X    while (st=stlist) {
X	stlist=st->next;
X	freeitlist(st->item);
X	xfree((char *)st);
X    }
X}
X
Xstatic void
Xopstlist(stlist)
XSTATE *stlist;
X{
X    void opstate();
X    STATE *st;
X
X    fitem=xopen(nitem,"wb");
X    cnincon=0;		/* Count of complete items in inconsistent states */
X    cncxst=0;		/* Count of complex states */
X    cncxit=0;		/* Count of complete items in complex states */
X    cnitem=0;		/* Count of all items */
X
X    for (st=stlist; st ; st=st->next) {
X	opstate(st);
X    }
X    putw(-1,fitem);	/* Eof indicator */
X    xclose(fitem,nitem);
X}
X
Xstatic void
Xopstate(st)
XSTATE *st;
X{
X    void dpitem();
X    ITEM *it;
X    int j,n,r;
X
X    trace(("State %u\n",st->num));
X
X    for (it=st->item,n=0,r=0,j=0; it && j <= 1;
X		it=(it->next) ? it->next : (++j,st->empty) ) {
X	putw(st->num,fitem);		/* Number of state containing item */
X	putw(rulesym[it->rule],fitem);	/* LHS Symbol (NB. Not valnont()) */
X	putw(it->rule,fitem);		/* Rule number */
X	putw(it->dposn,fitem);		/* Distinguished posn (0=complete) */
X
X#ifdef TRACE2
X	dpitem(it);
X#endif
X	++cnitem;			/* Number of items in all states */
X	++n;				/* Number of items in this state */
X	if (it->dposn == 0)
X	    ++r;			/* Complete items in this state */
X#ifdef TRACE2
X	printf("opstate: st->num=%d rulesym=%d it->rule=%d it->dposn=%d\n",
X	    st->num,rulesym[it->rule],it->rule,it->dposn);
X	printf("opstate: it=%08lx it->next=%08lx j=%d\n",
X		(long)it,(long)it->next,j);
X	printf("opstate: empty=%08lx new=%08lx\n",
X		(long)st->empty,(long)((it->next)?it->next:st->empty) );
X#endif
X    }
X
X    if (r && (n > 1)) {	/* Complete & any other items = inconsistent state */
X	cnincon+=r;	/* Count complete items in all inconsistent states */
X    }
X    if (r > 1) {	/* More than one complete item = complex state */
X	++cncxst;
X	cncxit+=r;
X    }
X}
X
X#ifdef TRACE2
X
Xstatic void
Xdpitem(it)
XITEM *it;
X{
X    int i,end,dposn;
X
X    end=lngrule(it->rule)+1;
X    dposn=it->dposn ? it->dposn : end;
X    printf("\t%s\t: ",namesym(rulesym[it->rule]));
X    for (i=1; i<dposn; ++i) {
X	printf("%s ",namesym(rhssym(it,i)));
X    }
X    printf("_ ");
X    for (i=dposn; i<end; ++i) {
X	printf("%s ",namesym(rhssym(it,i)));
X    }
X    printf("\n");
X}
X
X#endif
X
END_OF_FILE
if test 11591 -ne `wc -c <'yalr0.c'`; then
    echo shar: \"'yalr0.c'\" unpacked with wrong size!
fi
# end of 'yalr0.c'
fi
if test -f 'yaophead.c' ; then
  echo shar: Will not clobber existing file \"'yaophead.c'\"
else
echo shar: Extracting \"'yaophead.c'\" \( 1159 characters \)
sed "s/^X//" >'yaophead.c' <<'END_OF_FILE'
X/* Yaophead.c	14-Jan-87	Output miscellaneous defines */
X/* 21-Jan-87	yylval defined but NOT declared */
X/* 14-May-88 */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	ophead()
X
X	Statics:	dotable()
X*/
X
X#include <stdio.h>
X
X#define PHASE1
X
X#include "yadefs.h"
X
Xstatic char *t1[] = {
X	"#define yyclearin\tyychar=-1\n",
X	"#define yyerrok\t\tyyerrflag=0\n",
X	"#ifndef YYMAXDEPTH\n",
X	"#define YYMAXDEPTH\t150\n",
X	"#endif\n",
X	0
X};
X
Xstatic char *t2[] = {
X	"#ifndef YYSTYPE\n",
X	"#define YYSTYPE\t\tint\n",
X	"#endif\n",
X	0
X};
X
Xstatic char *t3[] = {
X	"extern YYSTYPE yylval;\n",
X	"YYSTYPE yyval;\n",
X	"typedef int yytabelem;\n",
X	"#define YYERRCODE\t256\n",
X	0
X};
X
Xvoid ophead()
X{
X    void dotable();
X
X    /* fytabc and fytabh already open */
X
X    dotable(t1,fytabc);
X    if (!g_typeon) {		/* Union has not been specified for YYSTYPE */
X	dotable(t2,fytabc);
X	if (o_define) {
X	    dotable(t2,fytabh);
X	}
X    }
X    dotable(t3,fytabc);
X}
X
Xstatic void
Xdotable(s,f)
Xchar **s;
XFILE *f;
X{
X    while (*s) {
X	fputs(*s++,f);
X    }
X}
X
END_OF_FILE
if test 1159 -ne `wc -c <'yaophead.c'`; then
    echo shar: \"'yaophead.c'\" unpacked with wrong size!
fi
# end of 'yaophead.c'
fi
if test -f 'yaoppars.c' ; then
  echo shar: Will not clobber existing file \"'yaoppars.c'\"
else
echo shar: Extracting \"'yaoppars.c'\" \( 935 characters \)
sed "s/^X//" >'yaoppars.c' <<'END_OF_FILE'
X/* Yaoppars.c	14-Jan-87	Add yypars.c and actions to ytab.c */
X/* 25-Jul-87 IBM */
X/* 30-Nov-88 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	oppars()
X*/
X
X#include <stdio.h>
X
X#define PHASE3
X
X#include "yadefs.h"
X
Xvoid
Xoppars()
X{
X    int c;
X
X    message("oppars:");
X
X    fytabc=xopen(nytabc,"a");
X    fyaccpar=xopen(nyaccpar,"r");
X
X    for (;;) {
X	if ((c=getc(fyaccpar)) == '$') {
X	    if ((c=getc(fyaccpar)) == 'A') {
X		faction=xopen(naction,"rb");
X		for (;;) {
X		    c=getc(faction);
X		    if (iseofchar(c)) break;
X		    putc(c,fytabc);
X		}
X		xclose(faction,naction);
X		continue;
X	    }
X	    else {
X		putc('$',fytabc);	/* And fall through to put c or eof */
X	    }
X	}
X	if (c == EOF) {
X	    break;
X	}
X	putc(c,fytabc);
X    }
X
X    xclose(fyaccpar,nyaccpar);
X    xclose(fytabc,nytabc);
X}
X
END_OF_FILE
if test 935 -ne `wc -c <'yaoppars.c'`; then
    echo shar: \"'yaoppars.c'\" unpacked with wrong size!
fi
# end of 'yaoppars.c'
fi
if test -f 'yaopsym.c' ; then
  echo shar: Will not clobber existing file \"'yaopsym.c'\"
else
echo shar: Extracting \"'yaopsym.c'\" \( 7153 characters \)
sed "s/^X//" >'yaopsym.c' <<'END_OF_FILE'
X/* Yaopsym.c	19-Oct-86	Output phase 1 symbol information */
X/* 25-Jul-87 IBM */
X/* 09-Jul-89 ZTC*/
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	opsym()
X
X	Uses:		enquote()
X*/
X
X#include <stdio.h>
X
X#define PHASE1
X
X#include "yadefs.h"
X
Xvoid opsym()				/* Output symbol definitions */
X{
X    char *enquote();
X
X    SYMBOL *s,*s0,*s1,*s2;
X    RULE *r,*r2;
X    LIST *l,*l2;
X    int i,i2;
X    int nontnum;
X    int swap;
X    char *p,*p2,buf[13],leadch;
X    int symseq,stroff,ruleoff,rhsoff;
X
X    message("opsym:");
X
X    nontnum=bsnont;			/* Give all nonterminals a toknum */
X    cnstr=0;				/* Find length of string area */
X    s=shead;
X    while (s) {
X	if (s->kind == NONT) {
X	    s->toknum=nontnum++;
X	}
X	if (s->kind == NONT || s->kind == TOKEN) {
X	    cnstr+=(strlen(s->name)+1);
X	}
X	s=s->lsym;
X    }
X
X    do {				/* Sort symbols by toknum */
X	swap=0;				/* Using bubble sort - yuck ! */
X	s0=NULL;
X	s1=shead;
X	s2=s1->lsym;			/* Assumes s1 != NULL */
X	while (s1 && s2) {
X	    if (s1->toknum <= s2->toknum) {
X		s0=s1;
X		s1=s2;
X		s2=s2->lsym;
X	    }
X	    else {
X		if (s0) {
X		    s0->lsym=s2;
X		}
X		else {
X		    shead=s2;
X		}
X		s1->lsym=s2->lsym;
X		s2->lsym=s1;
X		s0=s2;
X		s2=s1->lsym;
X		swap=1;
X	    }
X	}
X    } while (swap);
X
X    fsymbol=xopen(nsymbol,"wb");
X    fstring=xopen(nstring,"wb");
X
X    stroff=0;
X
X    putw(cnstr,fstring);
X    putw(cntok,fsymbol);
X    putw(cnnont,fsymbol);
X    putw(bstok,fsymbol);
X    putw(bsnont,fsymbol);
X
X    /* fytabc & fytabh already open */
X
X    fputs("\n",fytabc);
X    fputs("typedef struct { char *t_name; int t_val; } yytoktype;\n\n",fytabc);
X    fputs("#ifndef YYDEBUG\n#define YYDEBUG ",fytabc);
X    if (o_yydebug)
X	fputs("1",fytabc);
X    else
X	fputs("0",fytabc);
X    fputs(" /* allow debugging */\n#endif\n\n",fytabc);
X
X    fputs("#if YYDEBUG\n\n",fytabc);
X    fputs("yytoktype yytoks[] = {\n",fytabc);
X    leadch=' ';
X    s=shead;
X    while (s) {
X	if (s->kind == TOKEN
X	  && s->toknum != 0		/* not end of file */
X	  && s->toknum != 256		/* not error */
X	) {
X	    p=enquote(s->name);
X	    fprintf(fytabc,"\t%c%s,\t%d\n",leadch,p,s->toknum);
X	    xfree((char *)p);
X	    leadch=',';
X	}
X	s=s->lsym;
X    }
X    fprintf(fytabc,"\t%c\"-unknown-\",\t-1\n};\n",leadch);
X
X#ifdef NONTDESC
X    fputs("yytoktype yynonts[] = {\n",fytabc);
X    leadch=' ';
X    s=shead;
X    while (s) {
X	if (s->kind == NONT) {
X	    /* NB. non-terminals in output are numbered from zero */
X	    p=enquote(s->name);
X	    fprintf(fytabc,"\t%c%s,\t%d\n",leadch,p,s->toknum-257);
X	    xfree((char *)p);
X	    leadch=',';
X	}
X	s=s->lsym;
X    }
X    fprintf(fytabc,"\t%c\"-unknown-\",\t-1\n};\n",leadch);
X#endif
X
X    fputs("char *yyreds[] = {\n",fytabc);
X
X#ifdef RULEFROMONE
X    fprintf(fytabc,"\t\"-no such reduction-\"\n");
X    leadch=',';
X#else
X    leadch=' ';
X#endif
X    for (i=0; i<cnrule; ++i) {
X	i2=cnrule;		/* non-existent value */
X	s=shead;
X	while (s) {
X	    if (s->kind == NONT) {
X		r=s->rule;
X		while (r) {
X		    i2=r->seq;
X		    if (i2 == i) goto found;
X		    r=r->next;
X		}
X	    }
X	    s=s->lsym;
X	}
X	found:
X	if (i2 == i) {		/* found rule sequence number i */
X	    p=xalloc(strlen(r->sym->name)+3);
X	    strcpy(p,r->sym->name);
X	    strcat(p," :");
X	    for (l=r->list; l; l=l->next) {
X		p=xrealloc(p,strlen(p)+strlen(l->sym->name)+2);
X		strcat(p," ");
X		strcat(p,l->sym->name);
X	    }
X	    p2=enquote(p);
X	    fprintf(fytabc,"\t%c%s\n",leadch,p2);
X	    xfree((char *)p);
X	    xfree((char *)p2);
X	    leadch=',';
X	}
X    }
X    fprintf(fytabc,"};\n");
X
X    fputs("#endif /* YYDEBUG */\n\n",fytabc);
X
X    s=shead;
X    symseq=0;
X    while (s) {
X	if (s->kind == TOKEN) {
X	    p=s->name;
X	    do {			/* Output string INCLUDING null */
X		wrstrch(*p,fstring);
X	    } while (*p++);
X	    putw(stroff,fsymbol);
X	    stroff+=(strlen(s->name)+1);
X
X	    putw(s->toknum,fsymbol);
X	    putw(s->prec,fsymbol);
X	    putw(s->assoc,fsymbol);
X
X	    if (s->toknum >= bstok) {
X		fprintf(fytabc,"#define %s\t%d\n",s->name,s->toknum);
X		if (o_define)
X		    fprintf(fytabh,"#define %s\t%d\n",s->name,s->toknum);
X	    }
X	    s->toknum=symseq++;		/* Replace token number with token */
X					/* sequence (used in rules) */
X	}
X	s=s->lsym;
X    }
X
X    fputs("\n",fytabc);
X    if (o_define) fputs("\n",fytabh);
X
X    s=shead;				/* Sequence nonterminals for rules */
X    while (s) {
X	if (s->kind == NONT) {
X	    s->toknum=symseq++;
X	}
X	s=s->lsym;
X    }
X
X    /*	At this point toknum for both tokens and nonterminals has been
X	changed from the value of the token from the lexical analyzer
X	to a sequence number, corresponding to the sequence in the symbol
X	file, with:
X
X		tokens       having sequence from 0 to cntok-1
X		nonterminals having sequence from cntok onwards
X    */
X
X    frule=xopen(nrule,"wb");
X    frhs=xopen(nrhs,"wb");
X    ruleoff=0;
X    rhsoff=0;
X
X    putw(cnrule,frule);
X    putw(cntok,frule);			/* Used as sequence offset for nont */
X    putw(sstart->toknum,frule);		/* Sequence number of start nont */
X    putw(cnrhs,frhs);
X
X    s=shead;
X    while (s) {
X	if (s->kind == NONT) {
X	    p=s->name;
X	    do {			/* Output string INCLUDING null */
X		wrstrch(*p,fstring);
X	    } while (*p++);
X	    putw(stroff,fsymbol);
X	    stroff+=(strlen(s->name)+1);
X
X	    putw(ruleoff,fsymbol);
X
X	    r=s->rule;
X
X	    if (r == NULL) {
X		er2msg(s->name,"not declared as token and has no rule",FATAL);
X	    }
X	    while (r) {
X		++ruleoff;
X		putw(r->sym->toknum,frule);	/* Is really sym sequence */
X		putw(r->seq,frule);
X		putw(r->prec,frule);
X		putw(rhsoff,frule);
X
X		l=r->list;
X		while (l) {
X		    ++rhsoff;
X		    putw(l->sym->toknum,frhs);	/* Is really sym sequence */
X		    l=l->next;
X		}
X		r=r->next;
X	    }
X	}
X	s=s->lsym;
X    }
X
X    xclose(fsymbol,nsymbol);
X    xclose(fstring,nstring);
X    xclose(frule,nrule);
X    xclose(frhs,nrhs);
X
X#ifdef TRACE
X    s=shead;
X    while (s) {
X	switch (s->kind) {
X	    case NONT:
X		printf("NONT\tname:<%s> toknum:%u type:<%s>\n",
X		    s->name,s->toknum,(s->type) ? s->type : "**none**"
X		);
X		break;
X	    case TOKEN:
X		printf("name:<%s> assoc:%u prec:%u toknum:%u type:<%s>\n",
X		    s->name,s->assoc,s->prec,s->toknum,
X		    (s->type) ? s->type : "**none**"
X		);
X		break;
X	    default:
X		printf("kind:%u\tname:<%s>\n",s->kind,s->name);
X		break;
X	}
X	s=s->lsym;
X    }
X    s=shead;
X    while (s) {
X	if (s->kind == NONT) {
X	    r=s->rule;
X	    while (r) {
X		printf("prec:%u seq:%u\t%s : ",
X			r->prec,r->seq,r->sym->name);
X		l=r->list;
X		while (l) {
X		    printf("%s ",l->sym->name);
X		    l=l->next;
X		}
X		printf("\n");
X		r=r->next;
X	    }
X	}
X	s=s->lsym;
X    }
X    printf("%u tokens, %u nonterminals, %u rules, %u rhs symbols\n",
X	cntok,cnnont,cnrule,cnrhs);
X    printf("non-literal token base=%u and nonterminal base=%u\n",
X	bstok,bsnont);
X#endif
X
X    s=shead;
X    while (s) {
X	s2=s->lsym;
X	if (s->kind == NONT) {
X	    r=s->rule;
X	    while (r) {
X		r2=r->next;
X		l=r->list;
X		while (l) {
X		    l2=l->next;
X		    xfree((char *) l);
X		    l=l2;
X		}
X		xfree((char *) r);
X		r=r2;
X	    }
X	}
X	xfree((char *)s->name);
X	/* does not free s->union - not yet in use */
X	xfree((char *) s);
X	s=s2;
X    }
X    shead=NULL;
X}
X
END_OF_FILE
if test 7153 -ne `wc -c <'yaopsym.c'`; then
    echo shar: \"'yaopsym.c'\" unpacked with wrong size!
fi
# end of 'yaopsym.c'
fi
if test -f 'yapack.c' ; then
  echo shar: Will not clobber existing file \"'yapack.c'\"
else
echo shar: Extracting \"'yapack.c'\" \( 15512 characters \)
sed "s/^X//" >'yapack.c' <<'END_OF_FILE'
X/* Yapack.c	03-Dec-86	Pack transitions into action table */
X/* 25-Jul-87 IBM */
X/* 25-Mar-88 VAXVMS */
X/* 09-Jul-89 ZTC*/
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	pack()
X
X	Statics:	doshift()	dogoto()	clearv()
X			addv()		defv()		findspot()
X			bstart()	badvance()	gadvance()
X			vadvance()	loadspot()	gadd()
X			addend()	addfront()	joingroup()
X			isbase()	getshift()	getgoto()
X			ytact()		ytpgo()		ytpact()
X			ytchk()
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xtypedef struct group {		/* Group of entries in yxact[] */
X    struct group *next;
X    int start;			/* Start displacement */
X    int end;			/* End displacement */
X    struct tolist *toptr,	/* Head of list of tostates (the entries) */
X		  *tolast;	/* Tail of above */
X} GROUP;
X
Xtypedef struct tolist {		/* Group of sequential entries in yxact[] */
X    struct tolist *next;	/* Next entry in yxact[] */
X    int tostate;		/* Entry is destination of shift */
X} TOLIST;
X
Xtypedef struct vlist {		/* List of values read in for this state */
X    struct vlist *next;		/* Kept sorted by offset */
X    int tostate;
X    int offset;
X} VLIST;
X
Xstatic int *yxpact;		/* Index (base) to yxact for each state */
Xstatic int *yxpgo;		/* Index (base) to yxact for each nont */
Xstatic int *yxchk;		/* Symbol on entering state (DFA so unique) */
X
Xstatic int nnact;		/* Count of entries in yxact[] */
X
Xstatic int gttok;		/* Lookahead at entry in shift or goto file */
Xstatic int gtnont;
Xstatic int gtfrom;
Xstatic int gtto;
X
Xstatic int base;		/* Base of current spread in yxact[] */
Xstatic int low;			/* Lowest offset in current value */
X
Xstatic int gdispl;		/* Group displacement from yxact[0] */
Xstatic int vdispl;		/* value displacement from yxact[0] */
X
Xstatic int st;			/* State during shifts */
Xstatic int nont;		/* Nonterminal during gotos */
X
Xstatic GROUP *group;		/* Current group */
Xstatic GROUP *head;		/* First group in list */
X
Xstatic TOLIST *toptr;		/* Current position in groups tolist */
X
Xstatic VLIST *vhead;		/* Head of current states value list */
Xstatic VLIST *vptr;		/* Current entry in above */
X
Xstatic int bdispl;		/* Remember base position */
Xstatic GROUP *bgroup;
Xstatic TOLIST *btoptr;
X
X#define MAXACT 30000
X
X#define FINDGOTO	0	/* Mode values for findspot() */
X#define FINDSHIFT	1
X
X#ifdef TRACE
X#define	troff()	dpoff()
X#define tract() dpact()
Xstatic void dpoff();
Xstatic void dpact();
X#else
X#define	troff()
X#define tract()
X#endif
X
Xvoid
Xpack()
X{
X    void getshift(),doshift(),getgoto(),dogoto();
X    void clearv(),yttable();
X    int ytpgo(),ytact(),ytpact(),ytchk();
X    int i;
X
X    message("pack:");
X
X    yxpact=(int *)xalloc(cnstate*sizeof(int));
X    yxchk=(int *)xalloc(cnstate*sizeof(int));
X    yxpgo=(int *)xalloc(cnnont*sizeof(int));
X
X    for (i=0; i<cnstate; ++i) {
X	yxpact[i]=YXFLAG;
X	yxchk[i]=YXFLAG;
X    }
X    for (i=0; i<cnnont; ++i) {
X	yxpgo[i]=YXFLAG;
X    }
X
X    nnact= -1;				/* Deepest entry doesn't exist */
X					/* space to avoid old assign op */
X    head=NULL;				/* No groups to start with */
X
X    fshift=xopen(nshift,"rb");
X    vhead=NULL;				/* No value list yet */
X    getshift();				/* Lookahead */
X    nont=0;				/* isbase() doesn't check gotos yet */
X    for (st=0; st<cnstate; ++st) {
X	trace(("pack:doing st %d\n",st));
X	doshift();
X    }
X    xclose(fshift,nshift);
X
X    fgoto=xopen(ngoto,"rb");
X    clearv(&vhead);
X    getgoto();
X    st=cnstate;				/* Make isbase() check all states */
X    for (nont=0; nont<cnnont; ++nont) {
X	trace(("pack:doing nont %d\n",nont));
X	dogoto();
X    }
X    xclose(fgoto,ngoto);
X
X    ++nnact;				/* Was deepest entry - now is size */
X
X    trace(("pack: %d yxact[] entries\n",nnact));
X
X    fytabc=xopen(nytabc,"a");
X    yttable(fytabc,ytpgo,"yypgo",cnnont,TABLEWIDTH);
X    yttable(fytabc,ytpact,"yypact",cnstate,TABLEWIDTH);
X    yttable(fytabc,ytchk,"yychk",cnstate,TABLEWIDTH);
X    yttable(fytabc,ytact,"yyact",nnact,TABLEWIDTH);
X    fprintf(fytabc,"#define YYLAST %d\n",nnact);
X    xclose(fytabc,nytabc);
X}
X	
Xstatic void
Xdoshift()
X{
X    void clearv(),addv(),getshift(),loadspot();
X    int findspot();
X
X    if (gttok == -1 || gtfrom != st) {	/* No shifts for this state */
X	return;
X    }
X
X    clearv(&vhead);
X    low=bsnont-1;
X    while (gttok != -1 && gtfrom == st) {	/* Read in shifts */
X	trace(("doshift: tok %d from %d to %d\n",gttok,gtfrom,gtto));
X	yxchk[gtto]=gttok;		/* Check[] contains tok that gets us */
X					/* to the state */
X	addv(&vhead,gttok,gtto);
X	if (gttok < low) {
X	    low=gttok;
X	}
X	getshift();
X    }
X
X    if (findspot(FINDSHIFT)) {		/* Find a place for the values */
X	loadspot();			/* If not already all there, load */
X    }
X    yxpact[st]=base;
X}
X
Xstatic void
Xdogoto()
X{
X    void clearv(),addv(),defv(),getgoto(),loadspot();
X    int findspot();
X
X    if (gtnont == -1 || gtnont != nont) {	/* No gotos for this nont */
X	return;
X    }
X
X    clearv(&vhead);
X    low=0;					/* Always have default at 0 */
X    while (gtnont != -1 && gtnont == nont) {	/* Read in gotos */
X	trace(("dogoto: nont %d from %d to %d\n",gtnont,gtfrom,gtto));
X	yxchk[gtto]= -gtnont;		/* -ve to distinguish from tok */
X					/* space to avoid old assign op */
X	addv(&vhead,gtfrom+1,gtto);	/* +1 leaves space for 0 (default) */
X	getgoto();
X    }
X
X    defv(&vhead);			/* Find default and put at offset 0 */
X
X    if (findspot(FINDGOTO)) {		/* Find a place for the values */
X	loadspot();			/* If not already all there, load */
X    }
X    yxpgo[nont]=base;
X}
X
Xstatic void
Xclearv(ahead)
XVLIST **ahead;
X{
X    VLIST *new;
X
X    while (*ahead) {
X	new=(*ahead)->next;
X	xfree((char *)*ahead);
X	*ahead=new;
X    }
X}
X
Xstatic void
Xaddv(ahead,offset,tostate)
XVLIST **ahead;
Xint offset;
Xint tostate;
X{
X    VLIST *new,*spot,*last;
X
X    last=NULL;
X    for (spot= *ahead; spot && spot->offset < offset; spot=spot->next) {
X					/* "= *" avoids old assignment op */
X	last=spot;
X    }
X
X    if (spot && spot->offset == offset) {	/* Already in list */
X	return;
X    }
X
X    new=(VLIST *)xalloc(sizeof(VLIST));
X    new->next=spot;
X    new->offset=offset;
X    new->tostate=tostate;
X    
X    if (last) {				/* In middle of list */
X	last->next=new;
X    }
X    else {				/* New head of list */
X	*ahead=new;
X    }	    
X}
X
Xstatic void				/* Find default entry */
Xdefv(ahead)				/* ie. most frequent tostate */
XVLIST **ahead;
X{
X    void addv();
X
X    VLIST *ml,*l,*llast,*lnext;
X    int freq,mfreq,mtostate;
X
X    mfreq=0;
X    ml=NULL;
X    for (l= *ahead; l; l=l->next) {	/* Find most frequent tostate */
X					/* "= *" avoids old assignment op */
X	freq=1;
X	for (lnext=l->next; lnext; lnext=lnext->next) {
X	    if (l->tostate == lnext->tostate) {
X		++freq;
X	    }
X	}
X	if (freq >= mfreq) {		/* Use highest offset if choice */
X					/* to minimize spread */
X	    ml=l;
X	    mtostate=l->tostate;
X	}
X    }
X    llast=NULL;
X    for (l= *ahead; l; l=lnext) {	/* Delete any occurences of mtostate */
X					/* "= *" avoids old assignment op */
X	lnext=l->next;
X	if (l->tostate == mtostate) {
X	    if (llast) {
X		llast->next=lnext;
X	    }
X	    else {
X		*ahead=lnext;
X	    }
X	    xfree((char *)l);
X	}
X	else {
X	    llast=l;
X	}
X    }
X    addv(ahead,0,mtostate);		/* Replace it with default (offset 0)*/
X}
X
Xstatic int			/* Find a place to put the values */
Xfindspot(mode)			/* Returns 0 if already in place */
Xint mode;			/* FINDGOTO or FINDSHIFT - selects yxchk[] */
X{
X    void bstart(),badvance(),gadvance(),vadvance();
X    int isbase();
X    int chkval,range,clash,addreqd,donecant;
X
X    trace(("findspot:\n"));
X
X    base= -low;				/* space to avoid old assign op */ 
X    if (mode == FINDGOTO) {
X	chkval= -nont;			/* space to avoid old assign op */
X	range=base+cnstate;			/* Plus 0 default entry */
X    }
X    else {					/* chkval=gdispl-base(token) */
X	range=base+bsnont-1;
X    }
X    bstart();					/* Set group=head & save */
X
X    for (;;) {
X	trace(("findspot: new base\n"));
X	vptr=vhead;				/* Start from 1st value */
X	vdispl=vptr->offset+base;		/* Is always at least one */
X	addreqd=0;
X	clash=0;
X	donecant=0;
X	while (!clash && (vdispl <= range || gdispl <= range)) {
X	    trace(("findspot: another pass\n"));
X	    troff();
X	    if (gdispl == vdispl) {		/* value, in group */
X		trace(("findspot: value in group\n"));
X		if (toptr->tostate != vptr->tostate) {
X		    trace(("findspot:clash on to (is %d want %d)\n",
X			toptr->tostate,vptr->tostate));
X			clash=1;
X		}
X		else {
X		    gadvance();
X		    vadvance();
X		}
X	    }
X	    else {
X		if (gdispl < vdispl) {		/* No value, in group */
X		    if (mode == FINDSHIFT) {	/* Use token as yxchk[] */
X			chkval=gdispl-base;
X		    }				/* Else is -nont already */
X		    if (yxchk[toptr->tostate] == chkval) {
X			trace(("findspot: clash on check\n"));
X			clash=1;		/* Was ok, but we want error */
X		    }
X		    else {
X			gadvance();
X		    }
X		}
X		else { /* gdispl > vdispl */	/* value, in space */
X		    if (donecant++ == 0 && isbase(base)) {
X			trace(("findspot: clash on cantbe\n"));
X			clash=1;		/* Base already used */
X		    }
X		    else {
X			addreqd=1;		/* Need to load the space */
X			vadvance();
X		    }
X		}
X	    }
X	}
X	if (clash) {
X	    badvance();			/* Try next ++base (sets gdispl,etc) */
X	    ++range;
X	}
X	else {
X	    break;			/* Base is where to load */
X	}
X    }
X    return addreqd;
X}
X
Xstatic void				/* Start from base 0 or less */
Xbstart()				/* Sets b... and g... */
X{
X    if (group=head) {
X	gdispl=group->start;
X	toptr=group->toptr;
X    }
X    else {
X	gdispl=MAXACT;
X	toptr=NULL;
X    }
X    bgroup=group;			/* Remember the base */
X    bdispl=gdispl;
X    btoptr=toptr;
X}
X
Xstatic void				/* Advance base by one */
Xbadvance()				/* and set gdispl to start of base */
X{
X    void gadvance();
X
X    group=bgroup;			/* Restore old base */
X    gdispl=bdispl;
X    toptr=btoptr;
X    ++base;
X    while (gdispl < base) {		/* Advance if necessary */
X	gadvance();
X    }
X    bgroup=group;			/* Save new base for next time */
X    bdispl=gdispl;
X    btoptr=toptr;
X}
X
Xstatic void			/* Advance to next group member */
Xgadvance()			/* MUST NEVER be called if no groups */
X{
X    trace(("gadvance:\n"));
X    ++gdispl;
X    toptr=toptr->next;
X    if (gdispl > group->end) {
X	if (group->next) {
X	    group=group->next;
X	    gdispl=group->start;
X	    toptr=group->toptr;
X	}
X	else {
X	    gdispl=MAXACT;	/* NB. group unchanged */
X	    toptr=NULL;
X	}
X    }
X    troff();
X}
X
Xstatic void			/* Advance to next value, if exists */
Xvadvance()			/* MUST NEVER be called if no vptr */
X{
X    trace(("vadvance:\n"));
X    if (vptr=vptr->next) {
X	vdispl=vptr->offset+base;
X    }
X    else {
X	vdispl=MAXACT;
X    }
X    troff();
X}
X
Xstatic void				/* Load any values not already there */
Xloadspot()				/* From base (leaves base unchanged) */
X{
X    void gstart(),gadvance(),vadvance();
X    void gadd();
X
X    trace(("loadspot:\n"));
X    tract();
X
X    vptr=vhead;
X    vdispl=vptr->offset+base;
X    group=head;				/* NB. doesn't use bstart,badvance */
X
X    while (vptr) {
X	while (group && group->next && vdispl >= group->next->start) {
X	    group=group->next;
X	}
X	if (group == NULL || vdispl > group->end) {	/* value, in space */
X	    trace(("loadspot: space\n"));
X	    gadd(vdispl,vptr->tostate);
X	}
X	vadvance();			/* Has been loaded or already there */
X    }
X	
X    tract();
X}
X
Xstatic void
Xgadd(displ,tostate)
Xint displ;				/* Where new entry is */
Xint tostate;				/* To state of only entry in group */
X{
X    void joingroup(),addend(),addfront();
X    GROUP *g;
X
X    trace(("gadd:\n"));
X    tract();
X
X    g=NULL;					/* Use as flag */
X    if (group) {
X	if (group->end+1 == displ) {		/* Add to end of group */
X	    addend(group,tostate);
X	    g=group;
X	}
X	else {
X	    if (group->next && group->next->start == displ+1) {
X		addfront(group->next,tostate);	/* Add to front of next */
X		g=group->next;
X	    }
X	}
X    }
X
X    if (g == NULL) {				/* Need a new group */
X	g=(GROUP *)xalloc(sizeof(GROUP));
X	g->start=displ;
X	g->end=displ-1;
X	g->toptr=g->tolast=NULL;
X	addend(g,tostate);			/* Add to the end of empty */
X	if (group) {				/* Link it into the list */
X	    g->next=group->next;
X	    group->next=g;
X	}
X	else {
X	    head=g;
X	    g->next=NULL;
X	}
X	group=g;				/* We are now the last group */
X    }
X    else {					/* Added to existing group */
X	if (group->next && group->end+1 == group->next->start) {
X	    joingroup(group,group->next);	/* Coalesce adjacent groups */
X	}
X    }
X
X    if (displ > nnact) {
X	nnact=displ;				/* Remember deepest group */
X    }
X    troff();
X    tract();
X}
X
Xstatic void
Xaddend(group,tostate)			/* Add to end of groups tolist */
XGROUP *group;
Xint tostate;
X{
X    TOLIST *newto;
X
X    newto=(TOLIST *)xalloc(sizeof(TOLIST));
X    newto->tostate=tostate;
X    if (group->tolast) {		/* Add to end of tolist */
X	group->tolast->next=newto;
X    }
X    else {				/* Adding to empty tolist */
X	group->tolast=group->toptr=newto;
X    }
X    newto->next=NULL;			/* We are the last */
X    group->tolast=newto;
X    ++group->end;
X}
X
Xstatic void
Xaddfront(group,tostate)
XGROUP *group;
Xint tostate;
X{
X    TOLIST *newto;
X
X    newto=(TOLIST *)xalloc(sizeof(TOLIST));
X    newto->tostate=tostate;
X    newto->next=group->toptr;
X    group->toptr=newto;
X    if (group->tolast == NULL) {
X	group->tolast=newto;
X    }
X    --group->start;
X}
X
Xstatic void
Xjoingroup(g1,g2)
XGROUP *g1,*g2;
X{
X    trace(("joingroup:\n"));
X    tract();
X    g1->tolast->next=g2->toptr;
X    g1->tolast=g2->tolast;
X    g1->end=g2->end;
X    g1->next=g2->next;
X    xfree((char *)g2);
X    tract();
X}
X
Xstatic int				/* Has base already been used ? */
Xisbase(base)
Xint base;
X{
X    int i;
X
X    trace(("isbase: st %d nont %d base %d\n",st,nont,base));
X    for (i=0; i<st; ++i) {		/* Look at filled shift bases */
X	if (yxpact[i] == base) {
X	    trace(("isbase: yxpact[]==base\n"));
X	    return 1;
X	}
X    }
X    for (i=0; i<nont; ++i) {		/* Look at filled goto bases */
X	if (yxpgo[i] == base) {
X	    trace(("isbase: yxpgo[]==base\n"));
X	    return 1;
X	}
X    }
X    return 0;
X}
X
Xstatic void
Xgetshift()
X{
X    if ((gttok=getw(fshift)) != -1 ) {	/* Token (real value) */
X	gtfrom=getw(fshift);		/* From state (sorted on this) */
X	gtto=getw(fshift);		/* To state */
X    }
X}
X
Xstatic void
Xgetgoto()
X{
X    if ((gtnont=getw(fgoto)) != -1 ) {	/* Nont (real value)(sorted on this) */
X	gtfrom=getw(fgoto);		/* From state */
X	gtto=getw(fgoto);		/* To state */
X    }
X}
X
Xstatic int
Xytact(i)
Xint i;
X{
X    void bstart(),gadvance();
X    int r;
X
X    if (i == 0) {
X	base=0;
X	bstart();			/* Start at the beginning */
X    }
X    if (i == gdispl) {
X	r=toptr->tostate;
X	gadvance();
X	return r;
X    }
X    else {
X	return 0;			/* Space is filled with 0 */
X    }
X}
X
Xstatic int
Xytpgo(i)
Xint i;
X{
X    return yxpgo[i];
X}
X
Xstatic int
Xytpact(i)
Xint i;
X{
X    return yxpact[i];
X}
X
Xstatic int
Xytchk(i)
Xint i;
X{
X    return yxchk[i];
X}
X
X#ifdef TRACE
Xstatic void
Xdpoff()
X{
X    printf("bdispl %d bgroup %08lx btoptr %08lx\tbase %d low %d\n",
X	bdispl,(unsigned long)bgroup,(unsigned long)btoptr,base,low);
X    printf("gdispl %d  group %08lx  toptr %08lx",
X	gdispl,(unsigned long)group,(unsigned long)toptr);
X    if (group) {
X	printf("\tstart %d end %d",group->start,group->end);
X    }
X    printf("\nvdispl %d   vptr %08lx",vdispl,(unsigned long)vptr);
X    if (vptr) {
X	printf("\tvoffset %d vtostate %d",vptr->offset,vptr->tostate);
X    }
X    printf("\n");
X}
X
Xstatic void
Xdpact()
X{
X    void dpto();
X    GROUP *g;
X
X    g=head;
X    while (g) {
X	printf("%08lx: group\tstart %d end %d\n",
X	    (unsigned long)g,g->start,g->end);
X	dpto(g->toptr);
X	g=g->next;
X    }
X}
X
Xstatic void
Xdpto(t)
XTOLIST *t;
X{
X    while (t) {
X	printf("\t%08lx: to %d\n",(unsigned long)t,t->tostate);
X	t=t->next;
X    }
X}
X
X#endif
END_OF_FILE
if test 15512 -ne `wc -c <'yapack.c'`; then
    echo shar: \"'yapack.c'\" unpacked with wrong size!
fi
# end of 'yapack.c'
fi
if test -f 'yaparse.c' ; then
  echo shar: Will not clobber existing file \"'yaparse.c'\"
else
echo shar: Extracting \"'yaparse.c'\" \( 14729 characters \)
sed "s/^X//" >'yaparse.c' <<'END_OF_FILE'
X/* yacc version 0.05 July 9, 1989 1:53 AM */
X
X
X#line 1
X
X/* Yaparse.y	15-Jan-87 */
X/* 22-Jul-87 IBM */
X/* 09-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X#include <stdio.h>
X
X#define PHASE1
X
X#include "yadefs.h"
X
XRULE *addrule();
XSYMBOL *chksym();
Xvoid addlist(),setnont(),settok(),setnum();
Xvoid docommand();
X
X#define YYFULLERR	1	/* use lookahead dump on syntax error */
X
X
Xtypedef union {
X
X#line 27
X
X	int	u_int;
X	RULE	*u_rule;
X	SYMBOL	*u_symbol;
X} YYSTYPE;
X
Xtypedef struct { char *t_name; int t_val; } yytoktype;
X
X#ifndef YYDEBUG
X#define YYDEBUG 1 /* allow debugging */
X#endif
X
X#if YYDEBUG
X
Xyytoktype yytoks[] = {
X	 "\"Bad Character\"",	257
X	,"\"Literal\"",	258
X	,"\"Identifier\"",	259
X	,"\"Identifier then :\"",	260
X	,"\"Number\"",	261
X	,"\"%left\"",	262
X	,"\"%right\"",	263
X	,"\"%nonassoc\"",	264
X	,"\"%token\"",	265
X	,"\"%prec\"",	266
X	,"\"%type\"",	267
X	,"\"%start\"",	268
X	,"\"%union\"",	269
X	,"\"%%\"",	270
X	,"\"{ .. action .. }\"",	271
X	,"\"%{ .. definition .. %}\"",	272
X	,"\"{ .. union .. }\"",	273
X	,"\",\"",	274
X	,"\":\"",	275
X	,"\";\"",	276
X	,"\"|\"",	277
X	,"\"<\"",	278
X	,"\">\"",	279
X	,"\"-unknown-\"",	-1
X};
Xchar *yyreds[] = {
X	 "$accept : spec $end"
X	,"spec : flag0 defs MARK flag1 optbody rules"
X	,"flag0 :"
X	,"flag1 :"
X	,"optbody : DEFBODY"
X	,"optbody :"
X	,"defs : defs def"
X	,"defs :"
X	,"def : YSTART IDENTIFIER"
X	,"def : YUNION UNIONBODY"
X	,"def : DEFBODY"
X	,"def : rword tag nlist"
X	,"rword : YTOKEN"
X	,"rword : YLEFT"
X	,"rword : YRIGHT"
X	,"rword : YNONASSOC"
X	,"rword : YTYPE"
X	,"tag : LANGLE IDENTIFIER RANGLE"
X	,"tag :"
X	,"nlist : nmno"
X	,"nlist : nlist nmno"
X	,"nlist : nlist COMMA nmno"
X	,"nmno : idlit"
X	,"nmno : idlit NUMBER"
X	,"rules : rule"
X	,"rules : rules rule"
X	,"$$26 :"
X	,"rule : cid COLON $$26 rbody prec"
X	,"$$28 :"
X	,"rule : rule BAR $$28 rbody prec"
X	,"rbody : ract idlit"
X	,"rbody :"
X	,"ract : rbody"
X	,"ract : rbody ACTBODY"
X	,"prec : YPREC idlit"
X	,"prec : YPREC idlit ACTBODY"
X	,"prec : ACTBODY"
X	,"prec : prec SEMICOLON"
X	,"prec :"
X	,"cid : C_IDENTIFIER"
X	,"idlit : IDENTIFIER"
X	,"idlit : LITERAL"
X};
X#endif /* YYDEBUG */
X
X#define error	256
X#define BADCHAR	257
X#define LITERAL	258
X#define IDENTIFIER	259
X#define C_IDENTIFIER	260
X#define NUMBER	261
X#define YLEFT	262
X#define YRIGHT	263
X#define YNONASSOC	264
X#define YTOKEN	265
X#define YPREC	266
X#define YTYPE	267
X#define YSTART	268
X#define YUNION	269
X#define MARK	270
X#define ACTBODY	271
X#define DEFBODY	272
X#define UNIONBODY	273
X#define COMMA	274
X#define COLON	275
X#define SEMICOLON	276
X#define BAR	277
X#define LANGLE	278
X#define RANGLE	279
X
X#define yyclearin	yychar=-1
X#define yyerrok		yyerrflag=0
X#ifndef YYMAXDEPTH
X#define YYMAXDEPTH	150
X#endif
Xextern YYSTYPE yylval;
XYYSTYPE yyval;
Xtypedef int yytabelem;
X#define YYERRCODE	256
X
X#line 276
X
X
X/* yyerror(), yyterror() are defined in yautil.c */
X
Xyytabelem yydef[] = {
X	2, 7, -2, 0, 0, 3, 0, 0, 10, 18, 
X	12, 13, 14, 15, 16, 6, 5, 8, 9, 0, 
X	0, 4, 0, 0, 22, 40, 41, 19, 11, 0, 
X	24, 39, 1, 17, 23, 20, 0, 26, 28, 25, 
X	21, 31, 31, 0, -2, -2, 30, 0, -2, 27, 
X	29, 34, 37, 35
X};
Xyytabelem yyexca[] = {
X	-1, 2, 
X	0, -1, 
X	-2, 0, 
X	-1, 44, 
X	258, 32, 
X	259, 32, 
X	-2, 38, 
X	-1, 45, 
X	258, 32, 
X	259, 32, 
X	-2, 38, 
X	-1, 48, 
X	258, 33, 
X	259, 33, 
X	-2, 36
X};
Xyytabelem yyr1[] = {
X	0, 18, 8, 19, 7, 7, 17, 17, 6, 6, 
X	6, 6, 5, 5, 5, 5, 5, 4, 4, 3, 
X	3, 3, 16, 16, 15, 15, 2, 12, 1, 12, 
X	11, 11, 14, 14, 13, 13, 13, 13, 13, 10, 
X	9, 9
X};
Xyytabelem yyr2[] = {
X	2, 6, 0, 0, 1, 0, 2, 0, 2, 2, 
X	1, 3, 1, 1, 1, 1, 1, 3, 0, 1, 
X	2, 3, 1, 2, 1, 2, 0, 5, 0, 5, 
X	2, 0, 1, 2, 2, 3, 1, 2, 0, 1, 
X	1, 1
X};
Xyytabelem yypgo[] = {
X	-1000, 26, 27, 28, 29, 31, 32, 33, 34, 35, 
X	37, 38, 39, 40, 41, 42, 44, 43, 45, 46
X};
Xyytabelem yypact[] = {
X	-1000, -1000, -1000, -262, -1000, -1000, -255, -264, -1000, -267, 
X	-1000, -1000, -1000, -1000, -1000, -1000, -260, -1000, -1000, -246, 
X	-244, -1000, -243, -263, -242, -1000, -1000, -1000, -238, -257, 
X	-254, -1000, -243, -1000, -1000, -1000, -244, -1000, -1000, -254, 
X	-1000, -1000, -1000, -244, -241, -241, -1000, -244, -1000, -252, 
X	-252, -249, -1000, -1000
X};
Xyytabelem yychk[] = {
X	-1000, -8, -18, -17, -1000, 270, 268, 269, 272, -5, 
X	265, 262, 263, 264, 267, -6, -19, 259, 273, 278, 
X	-4, 272, -7, 259, -9, 259, 258, -16, -3, -10, 
X	-12, 260, -15, 279, 261, -16, 274, 275, 277, -12, 
X	-16, -2, -1, -14, -11, -11, -9, 266, 271, -13, 
X	-13, -9, 276, 271
X};
Xyytabelem yyact[] = {
X	11, 12, 13, 10, 17, 14, 6, 7, 5, 18, 
X	8, 19, 21, 23, 26, 25, 33, 31, 37, 34, 
X	26, 25, 53, 38, 52, 47, 42, 41, 28, 20, 
X	48, 9, 15, 22, 1, 51, 36, 29, 45, 39, 
X	50, 43, 32, 3, 40, 2, 16, 0, 0, 0, 
X	0, 0, 0, 0, 0, 0, 24, 0, 0, 0, 
X	0, 0, 30, 0, 24, 27, 0, 0, 0, 0, 
X	0, 0, 24, 35, 0, 0, 0, 0, 0, 46, 
X	44, 0, 0, 0, 0, 49
X};
X#define YYLAST 86
X/* yaccpar	19-Dec-86	Parser to interpret yacc output tables */
X/* 14-May-88 */
X
X#ifndef YYDEBUG
X#define YYDEBUG		1	/* debugging is available, but not on yet */
X#endif
X
X#ifndef YYFULLERR
X#define YYFULLERR 	0	/* full error messages are not available */
X#endif
X
X#ifndef YYUNION
X#define YYUNION 	0	/* 0 == C compiler supports union assignment */
X#endif
X
X#if YYDEBUG
X#define YYDESC	1
X#else
X#if YYFULLERR
X#define YYDESC	1
X#endif /* YYFULLERR */
X#endif /* YYDEBUG */
X
X#if YYDEBUG
Xstatic int yyyylex();	/* !!! */
X#else
X#define yyyylex()	yylex()
X#endif
X
Xstatic void yygetchar();
X
X#if YYDESC
Xstatic char *yydesc();
X#endif
X
X#if YYFULLERR
Xstatic void yyterror();
X#endif
X
X#if YYUNION
X#define _yyassign(to,from)	yyunion(&to,&from)
X#else
X#define	_yyassign(to,from)	(to=from)
X#endif
X
X#define YYFLAG		(-1000)
X#define YYERROR		goto yyerrlab
X#define YYACCEPT	return(0)
X#define YYABORT		return(1)
X
X#if YYDEBUG
Xint	yydebug=0;		/* set to 1 to turn on debugging */
X#endif
X
XYYSTYPE yyvalue[YYMAXDEPTH];	/* parser value stack */
Xint yystack[YYMAXDEPTH];	/* parser state stack */
Xint yychar=(-1);		/* current input token (-1 == none) */
Xint yynerrs=0;			/* number of errors */
Xint yyerrflag=0;		/* error recovery in progress */
X
Xyyparse()
X{
X    int yystate;
X    int *yypstack;
X    YYSTYPE *yypvalue;
X    int yyindex;
X    int *yyxi;
X    int yypush;
X
X    yystate=0;
X    yychar=(-1);
X    yynerrs=0;
X    yyerrflag=0;
X    yypstack= &yystack[-1];	/* beware of old assignment operators !!! */
X    yypvalue= &yyvalue[-1];
X    yypush=1;
X
X    for (;;) {
X	if (yypush) {		/* put a state and value onto the stack */
X#if YYDEBUG 
X	    if (yydebug)
X		printf("[yydebug] state %d, token %s\n",
X		    yystate,yydesc(yychar,yytoks));
X#endif
X	    if (++yypstack > &yystack[YYMAXDEPTH]) {
X		yyerror("yacc stack overflow");
X		YYABORT;
X	    }
X	    *yypstack=yystate;
X	    ++yypvalue;
X	    _yyassign(*yypvalue,yyval);
X	}
X
X	yyindex=yypact[yystate];
X	if (yyindex>YYFLAG
X	  && (yygetchar(),
X	       (yyindex+= yychar) >= 0 && yyindex < YYLAST
X               && yychk[ yyindex=yyact[ yyindex ] ] == yychar
X	     )
X          ) {			/* valid shift */
X	    yychar=(-1);
X	    _yyassign(yyval,yylval);
X	    yystate=yyindex;
X	    if (yyerrflag > 0) --yyerrflag;
X	    yypush=1;
X	}
X	else {			/* default state action */
X	    if ( (yyindex=yydef[yystate]) == -2 ) {
X		yygetchar();
X		/* look through exception table */
X#if YYDEBUG
X		if (yydebug)
X		    printf("[yydebug] on lookahead %s\n",
X			yydesc(yychar,yytoks));
X#endif
X		for (yyxi=yyexca; (*yyxi!=(-1))||(yyxi[1]!=yystate); yyxi+=2);
X		for (yyxi+=2; *yyxi >= 0 && *yyxi != yychar; yyxi+=2);
X		if ((yyindex=yyxi[1]) < 0) {
X#if YYDEBUG
X		    if (yydebug) printf("[yydebug] accept\n");
X#endif
X		    YYACCEPT;
X		}
X	    }
X
X	    if (yyindex == 0) {	/* error ... attempt to resume parsing */
X		switch(yyerrflag) {
X		    case 0:	/* brand new error */
X#if YYFULLERR
X			yyindex=yypact[yystate];
X			if (yyindex>YYFLAG && yyindex<YYLAST) {
X			    int token,index;
X			    for (index=(yyindex>0)?yyindex:0;
X			      index<YYLAST; ++index) {
X				token=index-yyindex;
X				if (yychk[yyact[index]] == token
X				  && token != YYERRCODE) {
X				    yyterror(yydesc(token,yytoks));
X				}
X			    }
X			}
X			yyterror(NULL);
X#else
X			yyerror("syntax error");
X#endif
Xyyerrlab:
X			++yynerrs;
X		    case 1:
X		    case 2:	/* incompletely recovered error */
X			yyerrflag=3;
X	/* find a state where "error" is a legal shift action */
X			yypush=0;	/* use as local flag */
X			while(yypstack >= yystack) {
X			    yyindex=yypact[*yypstack] +YYERRCODE;
X			    if ( yyindex>=0 && yyindex<YYLAST
X			      && yychk[yyact[yyindex]] == YYERRCODE) {
X				yystate=yyact[yyindex];	/* shift error */
X				yypush=1;
X				break;			/* ... out of loop */
X			    }
X			    else {		/* no shift on error */
X#if YYDEBUG
X				if (yydebug) printf(
X		"[yydebug] error recovery pops state %d, uncovers %d\n",
X					*yypstack,yypstack[-1]);
X#endif
X				--yypstack;		/* pop stack */
X				--yypvalue;
X			    }
X			}
X			if (!yypush)	/* no error shift state on stack */
X			    YYABORT;
X
X			break;		/* else stack error state */
X			
X		    case 3:		/* no shift yet; discard input char */
X#if YYDEBUG
X			if (yydebug)
X			    printf("[yydebug] error recovery discards %s\n",
X				yydesc(yychar,yytoks));
X#endif
X			if (yychar == 0) YYABORT;	/* don't discard EOF */
X			yychar=(-1);
X			yypush=0;	/* try again in SAME state */
X		}
X	    }
X	    else {		/* reduction by production yyindex */
X		YYSTYPE *yypvt;
X		int yynont;
X		int yyrule;
X
X		yyrule=yyindex;
X#if YYDEBUG
X		if (yydebug)
X		    printf("[yydebug] reduce by (%d) \"%s\"\n",
X			yyrule,yyreds[yyrule]);
X#endif
X		yypstack -= yyr2[yyrule];
X		yypvt=yypvalue;
X		yypvalue -= yyr2[yyrule];
X		_yyassign(yyval,yypvalue[1]);
X		/* consult goto table to find next state */
X		yynont=yyr1[yyrule];
X		yyindex=yypgo[yynont] + *yypstack + 1;
X		if (yyindex>=YYLAST
X		  || yychk[yystate=yyact[yyindex]] != -yynont)
X		    yystate=yyact[yypgo[yynont]];
X		switch(yyrule) {
X		    
Xcase 2: {
X
X#line 51
X
X			    g_typeon=0;			/* Type checking off */
X			    section=DEFINITIONS;
X			    curprec=0;
X			    bstok=bsnont=FIRSTTOKEN;
X			    cntok=cnnont=0;
X			    settok(chksym(ERRORNAME),NOTOKEN);
X			
X} break;
X
Xcase 3: {
X
X#line 62
X
X			    faction=xopen(naction,"wb");
X
X			    section=RULES;
X			    nextrule=1;
X			    cnrhs=0;
X			
X} break;
X
Xcase 8: {
X
X#line 80
X
X			    sstart=yypvt[0].u_symbol;
X			    setnont(sstart);
X			
X} break;
X
Xcase 9: {
X
X#line 85
X
X			    g_typeon=1;
X			
X} break;
X
Xcase 12: {
X
X#line 93
X
X			    command=TOKEN;
X			
X} break;
X
Xcase 13: {
X
X#line 97
X
X			    ++curprec;
X			    command=LEFT;
X			
X} break;
X
Xcase 14: {
X
X#line 102
X
X			    ++curprec;
X			    command=RIGHT;
X			
X} break;
X
Xcase 15: {
X
X#line 107
X
X			    ++curprec;
X			    command=NONASSOC;
X			
X} break;
X
Xcase 16: {
X
X#line 112
X
X			    command=TYPE;
X			
X} break;
X
Xcase 17: {
X
X#line 118
X
X			    curtype=yypvt[-1].u_symbol->name;
X			    g_typeon=1;			/* Type checking on */
X			
X} break;
X
Xcase 18: {
X
X#line 123
X
X			    curtype=NOTYPE;
X			
X} break;
X
Xcase 22: {
X
X#line 134
X
X			    docommand(yypvt[0].u_symbol,NOTOKEN);
X			
X} break;
X
Xcase 23: {
X
X#line 138
X
X			    docommand(yypvt[-1].u_symbol,atoi(yypvt[0].u_symbol->name));
X			
X} break;
X
Xcase 24: {
X
X#line 144
X
X			    if (sstart == NULL) {/* Start defaults to rule 1 */
X				sstart=yypvt[0].u_rule->sym;
X			    }
X			
X} break;
X
Xcase 26: {
X
X#line 153
X g_offset=0; g_cid=yypvt[-1].u_symbol; 
X} break;
X
Xcase 27: {
X
X#line 155
X
X			    yypvt[-1].u_rule->next=yypvt[-4].u_symbol->rule;		/* before existing */
X			    yypvt[-4].u_symbol->rule=yypvt[-1].u_rule;		/* ie. is new head */
X			    yypvt[-1].u_rule->sym=yypvt[-4].u_symbol;			/* link back */
X			    if (yypvt[0].u_int) {			/* explicit prec */
X				yypvt[-1].u_rule->prec=yypvt[0].u_int;
X			    }
X			    yypvt[-1].u_rule->seq=nextrule++;		/* AFTER embedded */
X							/* actions done */
X			    yyval.u_rule=yypvt[-1].u_rule;
X			
X} break;
X
Xcase 28: {
X
X#line 167
X g_offset=0; 
X} break;
X
Xcase 29: {
X
X#line 169
X
X			    yypvt[-1].u_rule->next=yypvt[-4].u_rule;		/* Before existing */
X			    yypvt[-4].u_rule->sym->rule=yypvt[-1].u_rule;		/* New head */
X			    yypvt[-1].u_rule->sym=yypvt[-4].u_rule->sym;		/* Backward link */
X			    if (yypvt[0].u_int) {			/* explicit prec */
X			    	yypvt[-1].u_rule->prec=yypvt[0].u_int;
X			    }
X			    yypvt[-1].u_rule->seq=nextrule++;
X			    yyval.u_rule=yypvt[-1].u_rule;
X			
X} break;
X
Xcase 30: {
X
X#line 182
X
X			    addlist(yypvt[-1].u_rule,yypvt[0].u_symbol);
X			    switch (yypvt[0].u_symbol->kind) {
X				case TOKEN:	/* Rightmost is default prec */
X					yypvt[-1].u_rule->prec=yypvt[0].u_symbol->prec;
X					break;
X				case NONT:
X					break;
X				default:	/* Forces check for rule */
X					setnont(yypvt[0].u_symbol);
X					break;
X			    }
X			
X    			    yyval.u_rule=yypvt[-1].u_rule;
X			    ++g_offset;
X			
X} break;
X
Xcase 31: {
X
X#line 199
X
X			    yyval.u_rule=g_rule=addrule((SYMBOL *)NULL);
X			
X} break;
X
Xcase 32: {
X
X#line 205
X
X			    yyval.u_rule=yypvt[0].u_rule;
X			
X} break;
X
Xcase 33: {
X
X#line 209
X
X			    /* Deal with embedded action & */
X			    /* ++nextrule while lookahead is */
X			    /* idlit not next action */
X
X			    RULE *r;
X			    SYMBOL *sym;
X			    static char name[13] = "$$";
X
X			    itoa(nextrule,&name[2],10);	/* Use seq number */
X			    sym=chksym(name);
X			    setnont(sym);		/* As dummy nont */
X			    sym->rule=r=addrule(sym);
X			    r->sym=sym;
X			    r->seq=nextrule++;
X			    r->next=NULL;
X			
X			    addlist(yypvt[-1].u_rule,sym);		/* Insert dummy sym */
X			
X    			    yyval.u_rule=yypvt[-1].u_rule;
X			
X			    ++g_offset;
X			
X} break;
X
Xcase 34: {
X
X#line 235
X
X			    yyval.u_int=precok(yypvt[0].u_symbol);
X			
X} break;
X
Xcase 35: {
X
X#line 239
X
X			    yyval.u_int=precok(yypvt[-1].u_symbol);
X			
X} break;
X
Xcase 36: {
X
X#line 243
X
X			    yyval.u_int=0;	/* No precedence specified */
X			
X} break;
X
Xcase 37: {
X
X#line 247
X
X			    yyval.u_int=yypvt[-1].u_int;
X			
X} break;
X
Xcase 38: {
X
X#line 251
X
X			    yyval.u_int=0;
X			
X} break;
X
Xcase 39: {
X
X#line 258
X
X			    setnont(yypvt[0].u_symbol);
X			    yyval.u_symbol=yypvt[0].u_symbol;
X			
X} break;
X
Xcase 40: {
X
X#line 265
X
X			    yyval.u_symbol=yypvt[0].u_symbol;
X			
X} break;
X
Xcase 41: {
X
X#line 269
X
X			    /* settok() is performed in lexical analyzer */
X			    /* token number is char value */
X			    yyval.u_symbol=yypvt[0].u_symbol;
X			
X} break;
X
X		}
X		yypush=1;	/* stack new state and value */
X	    }
X	}
X    }
X}
X
X
Xstatic void
Xyygetchar()
X{
X    if (yychar < 0) if ((yychar=yyyylex()) < 0) yychar=0;
X}
X
X#if YYDEBUG
X
Xstatic int
Xyyyylex()
X{
X    int ch;
X
X    ch=yylex();
X    if (yydebug)
X	printf("[yydebug] received token %s\n",yydesc(ch,yytoks));
X    return ch;
X}
X
X#endif /* YYDEBUG */
X
X#if YYDESC
X
Xstatic char *
Xyydesc(ch,table)
Xint ch;
Xyytoktype *table;
X{
X    register yytoktype *p;
X    char *s;
X
X    if (ch == 0)
X	s="end-of-file";
X    else if (ch < 0)
X	s="-none-";
X    else {
X	for (p=table; p->t_val != ch && p->t_val >= 0; ++p);
X	s=p->t_name;
X    }
X    return s;
X}
X
X#endif /* YYDESC */
X
END_OF_FILE
if test 14729 -ne `wc -c <'yaparse.c'`; then
    echo shar: \"'yaparse.c'\" unpacked with wrong size!
fi
# end of 'yaparse.c'
fi
if test -f 'yaparse.sed' ; then
  echo shar: Will not clobber existing file \"'yaparse.sed'\"
else
echo shar: Extracting \"'yaparse.sed'\" \( 1332 characters \)
sed "s/^X//" >'yaparse.sed' <<'END_OF_FILE'
Xs/"BADCHAR"/"\\"Bad Character\\""/
Xs/"LITERAL"/"\\"Literal\\""/
Xs/"IDENTIFIER"/"\\"Identifier\\""/
Xs/"C_IDENTIFIER"/"\\"Identifier then :\\""/
Xs/"NUMBER"/"\\"Number\\""/
Xs/"YLEFT"/"\\"%left\\""/
Xs/"YRIGHT"/"\\"%right\\""/
Xs/"YNONASSOC"/"\\"%nonassoc\\""/
Xs/"YTOKEN"/"\\"%token\\""/
Xs/"YPREC"/"\\"%prec\\""/
Xs/"YTYPE"/"\\"%type\\""/
Xs/"YSTART"/"\\"%start\\""/
Xs/"YUNION"/"\\"%union\\""/
Xs/"MARK"/"\\"%%\\""/
Xs/"ACTBODY"/"\\"{ .. action .. }\\""/
Xs/"DEFBODY"/"\\"%{ .. definition .. %}\\""/
Xs/"UNIONBODY"/"\\"{ .. union .. }\\""/
Xs/"COMMA"/"\\",\\""/
Xs/"COLON"/"\\":\\""/
Xs/"SEMICOLON"/"\\";\\""/
Xs/"BAR"/"\\"|\\""/
Xs/"LANGLE"/"\\"<\\""/
Xs/"RANGLE"/"\\">\\""/
Xs/"-unknown-"/"\\"-unknown-\\""/
Xs/"BADCHAR"/"\"Bad Character\""/
Xs/"LITERAL"/"\"Literal\""/
Xs/"IDENTIFIER"/"\"Identifier\""/
Xs/"C_IDENTIFIER"/"\"Identifier then :\""/
Xs/"NUMBER"/"\"Number\""/
Xs/"YLEFT"/"\"%left\""/
Xs/"YRIGHT"/"\"%right\""/
Xs/"YNONASSOC"/"\"%nonassoc\""/
Xs/"YTOKEN"/"\"%token\""/
Xs/"YPREC"/"\"%prec\""/
Xs/"YTYPE"/"\"%type\""/
Xs/"YSTART"/"\"%start\""/
Xs/"YUNION"/"\"%union\""/
Xs/"MARK"/"\"%%\""/
Xs/"ACTBODY"/"\"{ .. action .. }\""/
Xs/"DEFBODY"/"\"{ .. definition .. }\""/
Xs/"UNIONBODY"/"\"{ .. union .. }\""/
Xs/"COMMA"/"\",\""/
Xs/"COLON"/"\":\""/
Xs/"SEMICOLON"/"\";\""/
Xs/"BAR"/"\"|\""/
Xs/"LANGLE"/"\"<\""/
Xs/"RANGLE"/"\">\""/
Xs/"-unknown-"/"\"-unknown-\""/
END_OF_FILE
if test 1332 -ne `wc -c <'yaparse.sed'`; then
    echo shar: \"'yaparse.sed'\" unpacked with wrong size!
fi
# end of 'yaparse.sed'
fi
if test -f 'yaparse.y' ; then
  echo shar: Will not clobber existing file \"'yaparse.y'\"
else
echo shar: Extracting \"'yaparse.y'\" \( 4461 characters \)
sed "s/^X//" >'yaparse.y' <<'END_OF_FILE'
X%{
X/* Yaparse.y	15-Jan-87 */
X/* 22-Jul-87 IBM */
X/* 09-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X#include <stdio.h>
X
X#define PHASE1
X
X#include "yadefs.h"
X
XRULE *addrule();
XSYMBOL *chksym();
Xvoid addlist(),setnont(),settok(),setnum();
Xvoid docommand();
X
X#define YYFULLERR	1	/* use lookahead dump on syntax error */
X
X%}
X
X%start spec
X
X%union {
X	int	u_int;
X	RULE	*u_rule;
X	SYMBOL	*u_symbol;
X}
X
X%token	BADCHAR
X%token	<u_symbol> LITERAL IDENTIFIER C_IDENTIFIER NUMBER
X%token	YLEFT YRIGHT YNONASSOC YTOKEN YPREC YTYPE YSTART YUNION
X	MARK ACTBODY DEFBODY UNIONBODY
X	COMMA COLON SEMICOLON BAR LANGLE RANGLE
X
X%type	<u_int> prec
X%type	<u_rule> rule rbody ract
X%type	<u_symbol> cid idlit
X
X%%
X
X/* NB. Endmarker is returned after rules, the tail is dealt with elsewhere */
X
Xspec	:	flag0 defs MARK flag1 optbody rules
X	;
X
Xflag0	:
X			{
X			    g_typeon=0;			/* Type checking off */
X			    section=DEFINITIONS;
X			    curprec=0;
X			    bstok=bsnont=FIRSTTOKEN;
X			    cntok=cnnont=0;
X			    settok(chksym(ERRORNAME),NOTOKEN);
X			}
X	;
X
Xflag1	:
X			{
X			    faction=xopen(naction,"wb");
X
X			    section=RULES;
X			    nextrule=1;
X			    cnrhs=0;
X			}
X	;
X
Xoptbody	:	DEFBODY			/* allow code at head of rules */
X	|
X	;
X
Xdefs	:	defs def
X	|						/* empty */
X	;
X
Xdef	:	YSTART IDENTIFIER
X			{
X			    sstart=$2;
X			    setnont(sstart);
X			}
X	|	YUNION UNIONBODY
X			{
X			    g_typeon=1;
X			}
X	|	DEFBODY
X	|	rword tag nlist
X	;
X
Xrword	:	YTOKEN
X			{
X			    command=TOKEN;
X			}
X	|	YLEFT
X			{
X			    ++curprec;
X			    command=LEFT;
X			}
X	|	YRIGHT
X			{
X			    ++curprec;
X			    command=RIGHT;
X			}
X	|	YNONASSOC
X			{
X			    ++curprec;
X			    command=NONASSOC;
X			}
X	|	YTYPE
X			{
X			    command=TYPE;
X			}
X	;
X
Xtag	:	LANGLE IDENTIFIER RANGLE
X			{
X			    curtype=$2->name;
X			    g_typeon=1;			/* Type checking on */
X			}
X	|						/* empty */
X			{
X			    curtype=NOTYPE;
X			}
X	;
X
Xnlist	:	nmno
X	|	nlist nmno
X	|	nlist COMMA nmno
X	;
X
Xnmno	:	idlit
X			{
X			    docommand($1,NOTOKEN);
X			}
X	|	idlit NUMBER
X			{
X			    docommand($1,atoi($2->name));
X			}
X	;
X
Xrules	:	rule
X			{
X			    if (sstart == NULL) {/* Start defaults to rule 1 */
X				sstart=$1->sym;
X			    }
X			}
X	|	rules rule
X	;
X
Xrule	:	cid COLON
X			{ g_offset=0; g_cid=$1; }
X		rbody prec
X			{
X			    $4->next=$1->rule;		/* before existing */
X			    $1->rule=$4;		/* ie. is new head */
X			    $4->sym=$1;			/* link back */
X			    if ($5) {			/* explicit prec */
X				$4->prec=$5;
X			    }
X			    $4->seq=nextrule++;		/* AFTER embedded */
X							/* actions done */
X			    $$=$4;
X			}
X	|	rule BAR
X			{ g_offset=0; }
X		rbody prec
X			{
X			    $4->next=$1;		/* Before existing */
X			    $1->sym->rule=$4;		/* New head */
X			    $4->sym=$1->sym;		/* Backward link */
X			    if ($5) {			/* explicit prec */
X			    	$4->prec=$5;
X			    }
X			    $4->seq=nextrule++;
X			    $$=$4;
X			}
X	;
X
Xrbody	:	ract idlit
X			{
X			    addlist($1,$2);
X			    switch ($2->kind) {
X				case TOKEN:	/* Rightmost is default prec */
X					$1->prec=$2->prec;
X					break;
X				case NONT:
X					break;
X				default:	/* Forces check for rule */
X					setnont($2);
X					break;
X			    }
X			
X    			    $$=$1;
X			    ++g_offset;
X			}
X	|						/* empty */
X			{
X			    $$=g_rule=addrule((SYMBOL *)NULL);
X			}
X	;
X
Xract	:	rbody
X			{
X			    $$=$1;
X			}
X	|	rbody ACTBODY
X			{
X			    /* Deal with embedded action & */
X			    /* ++nextrule while lookahead is */
X			    /* idlit not next action */
X
X			    RULE *r;
X			    SYMBOL *sym;
X			    static char name[13] = "$$";
X
X			    itoa(nextrule,&name[2],10);	/* Use seq number */
X			    sym=chksym(name);
X			    setnont(sym);		/* As dummy nont */
X			    sym->rule=r=addrule(sym);
X			    r->sym=sym;
X			    r->seq=nextrule++;
X			    r->next=NULL;
X			
X			    addlist($1,sym);		/* Insert dummy sym */
X			
X    			    $$=$1;
X			
X			    ++g_offset;
X			}
X	;
X
Xprec	:	YPREC idlit
X			{
X			    $$=precok($2);
X			}
X	|	YPREC idlit ACTBODY
X			{
X			    $$=precok($2);
X			}
X	|	ACTBODY
X			{
X			    $$=0;	/* No precedence specified */
X			}
X	|	prec SEMICOLON
X			{
X			    $$=$1;
X			}
X	|						/* empty */
X			{
X			    $$=0;
X			}
X	;
X
X
Xcid	:	C_IDENTIFIER
X			{
X			    setnont($1);
X			    $$=$1;
X			}
X	;
X
Xidlit	:	IDENTIFIER
X			{
X			    $$=$1;
X			}
X	|	LITERAL
X			{
X			    /* settok() is performed in lexical analyzer */
X			    /* token number is char value */
X			    $$=$1;
X			}
X	;
X
X%%
X
X/* yyerror(), yyterror() are defined in yautil.c */
X
END_OF_FILE
if test 4461 -ne `wc -c <'yaparse.y'`; then
    echo shar: \"'yaparse.y'\" unpacked with wrong size!
fi
# end of 'yaparse.y'
fi
if test -f 'yapcdos.h' ; then
  echo shar: Will not clobber existing file \"'yapcdos.h'\"
else
echo shar: Extracting \"'yapcdos.h'\" \( 2729 characters \)
sed "s/^X//" >'yapcdos.h' <<'END_OF_FILE'
X/* yapcdos.h 08-Jul-89 Implementation dependent things for IBM PC DOS */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X#ifdef __ZTC__
X#define SYSTEM	 "PC-DOS ZTC (file)"
X#else
X#define SYSTEM	 "PC-DOS (file)"
X#endif
X
X#define PCDOS
X
X#ifdef __ZTC__
X
X#define STDLIBHEAD	<stdlib.h>	/* define if stdlib.h needed */
X#define	STRINGHEAD	<string.h>	/* define if string.h needed */
X#define	TIMEHEAD	<time.h>	/* define if time.h needed */
X
X#else	/* assume Aztec C */
X
Xchar *malloc();
Xchar *realloc();
X
Xtypedef long clock_t;
X#define	clock()		(0l)
X
X#endif
X
X#ifdef __ZTC__
X#define TTYHEAD	<io.h>		/* define only if isatty() needs io.h */
X#else	/* assume Aztec C */
X#define TTYHEAD	<sgtty.h>	/* define only if isatty() needs sgtty.h */
X#endif
X
X#define	iseofchar(c)	( c == EOF || c == 0x1a )	/* ctrl-Z */
X
X#define BITSTR	unsigned int	/* Type of word used for bit strings */
X
X#define SORTTABLE	3000	/* size of pointer table in txsort() */
X				/* larger -> longer runs */
X#ifdef __ZTC__
X#define	NEEDGETW		/* include x...w() in yautil.c */
X#define	getw(f)		xgetw(f)
X#define	putw(u,f)	xputw(u,f)
X#define	rdstrch(f)	xgetw(f)
X#define	wrstrch(u,f)	xputw(u,f)
X#else	/* assume Aztec C */
X#define	rdstrch(f)	getc(f)
X#define	wrstrch(u,f)	putc(u,f)
X#endif
X
X/* set PATHSEPARATOR to null string "" if paths not implemented */
X#ifndef PATHSEPARATOR
X#define	PATHSEPARATOR	"\\"
X#endif
X
X/* leave TMPENVPATH undefined if compiler can't access environment */
X#ifndef TMPENVPATH			/* if not defined on compile line */
X#define	TMPENVPATH	"TMP"		/* where to find path for temp files */
X#endif
X/* set TMPDEFPATH to null string "" (current directory) if no paths */
X#ifndef TMPDEFPATH			/* if not defined on compile line */
X#define TMPDEFPATH	""		/* path to use if not in environment */
X#endif
X
X/* leave SKELENVPATH undefined if compiler can't access environment */
X#ifndef SKELENVPATH			/* if not defined on compile line */
X#define	SKELENVPATH	"YYSKELETON"	/* where to find path for skeleton */
X#endif
X/* set SKELDEFPATH to null string "" (current directory) if no paths */
X#ifndef SKELDEFPATH			/* if not defined on compile line */
X#define SKELDEFPATH	"c:\\util"	/* path to use if not in environment */
X#endif
X#ifndef SKELDEFNAME			/* if not defined on compile line */
X#define SKELDEFNAME	"yaccpar"	/* path to use if not in environment */
X#endif
X
X#ifndef YTABHDEFNAME			/* if not defined on compile line */
X#define	YTABHDEFNAME	"ytab.h"
X#endif
X#ifndef YTABCDEFNAME			/* if not defined on compile line */
X#define	YTABCDEFNAME	"ytab.c"
X#endif
X#ifndef YOUTDEFNAME			/* if not defined on compile line */
X#define	YOUTDEFNAME	"youtput"
X#endif
END_OF_FILE
if test 2729 -ne `wc -c <'yapcdos.h'`; then
    echo shar: \"'yapcdos.h'\" unpacked with wrong size!
fi
# end of 'yapcdos.h'
fi
if test -f 'yardprec.c' ; then
  echo shar: Will not clobber existing file \"'yardprec.c'\"
else
echo shar: Extracting \"'yardprec.c'\" \( 1248 characters \)
sed "s/^X//" >'yardprec.c' <<'END_OF_FILE'
X/* Yardprec.c	27-Nov-86	Read in precedence/associativity */
X/* 25-Jul-87 IBM */
X/* 30-Nov-88 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	rdprec()
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xvoid
Xrdprec()
X{
X    int i;
X
X    message("rdprec:");
X
X    fsymbol=xopen(nsymbol,"rb");	/* Read symbols */
X
X    (void)getw(fsymbol);
X    (void)getw(fsymbol);
X    (void)getw(fsymbol);
X    (void)getw(fsymbol);
X
X    toknum=(int *)xalloc(cntok*sizeof(int));
X    tokprec=(int *)xalloc(cntok*sizeof(int));
X    tokassoc=(int *)xalloc(cntok*sizeof(int));
X
X    for (i=0; i < cntok; ++i) {
X	(void)getw(fsymbol);
X	toknum[i]=getw(fsymbol);
X	tokprec[i]=getw(fsymbol);
X	tokassoc[i]=getw(fsymbol);
X    }
X
X    xclose(fsymbol,nsymbol);
X
X    frule=xopen(nrule,"rb");		/* Read rules */
X
X    (void)getw(frule);
X    (void)getw(frule);
X    (void)getw(frule);
X
X    ruleseq=(int *)xalloc(cnrule*sizeof(int));
X    ruleprec=(int *)xalloc(cnrule*sizeof(int));
X
X    for (i=0; i<cnrule; ++i) {
X	(void)getw(frule);
X	ruleseq[i]=getw(frule);
X	ruleprec[i]=getw(frule);
X	(void)getw(frule);
X    }
X    xclose(frule,nrule);
X}
X
END_OF_FILE
if test 1248 -ne `wc -c <'yardprec.c'`; then
    echo shar: \"'yardprec.c'\" unpacked with wrong size!
fi
# end of 'yardprec.c'
fi
if test -f 'yardtx.c' ; then
  echo shar: Will not clobber existing file \"'yardtx.c'\"
else
echo shar: Extracting \"'yardtx.c'\" \( 2613 characters \)
sed "s/^X//" >'yardtx.c' <<'END_OF_FILE'
X/* Yardtx.c	03-Nov-86	Read transitions for lookahead */
X/* 25-Jul-87 IBM */
X/* 30-Nov-88 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	rdtx()
X
X	Statics:	[dptx(),dpdread() - TRACE]
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xvoid
Xrdtx()				/* Read transitions */
X{
X    void dpdread(),dptx();
X
X    int v1,v2,v3;
X    int sym,st,i,swap;
X
X    message("rdtx:");
X
X    ftrans=xopen(ntrans,"rb");
X
X    trace(("rdtx: allocating ntxtab size cnntx %u * size %u = %u\n",
X	cnntx,sizeof(NTXTAB),cnntx*sizeof(NTXTAB)));
X    ntxtab=(NTXTAB *)xalloc(cnntx*sizeof(NTXTAB));
X    trace(("rdtx: allocating dread size cnstate %u * size %u = %u\n",
X	cnstate,sizeof(BITSTR *),cnstate*sizeof(BITSTR *)));
X    dread=(BITSTR **)xalloc(cnstate*sizeof(BITSTR *));
X    trace(("rdtx: allocating cnstate %u bit vectors length cntok %u\n",
X	cnstate,cntok));
X    for (i=0; i<cnstate; ++i) {		/* dread is indexed by state */
X	dread[i]=alcbit(cntok);		/* bit vector is indexed by token */
X	zerobit(dread[i],cntok);
X    }
X
X    st=-1;
X    sym=-1;
X    i=0;
X    for (;;) {
X	if ((v1=getw(ftrans)) == -1) {	/* Symbol */
X	    break;			/* Eof indicator */
X	}
X	v2=getw(ftrans);		/* From state (sorted on this) */
X	v3=getw(ftrans);		/* To state */
X	(void)getw(ftrans);		/* Ignore rule */
X	(void)getw(ftrans);		/* Ignore dposn */
X
X	if (sym == v1 && st == v2) {	/* Ignore additional entries (rules) */
X					/* Don't need to check to state */
X	    trace(("rdtx: ignore (to is %u)\n",v3));
X	    continue;
X	}
X	sym=v1;
X	st=v2;
X
X	if (isnont(v1)) {
X	    trace(("rdtx: nont tx on %s from %u to %u\n",namesym(v1),v2,v3));
X	    ntxtab[i].nont=valnont(v1);	/* ie. file contains symbol not nont */
X	    ntxtab[i].from=v2;
X	    ntxtab[i].to=v3;
X	    ++i;
X	}
X	else {				/* Dread=Token transition from state */
X	    trace(("rdtx: token tx on %s from %u to %u\n",namesym(v1),v2,v3));
X	    setbit(dread[v2],valtok(v1));
X	}
X    }
X
X    xclose(ftrans,ntrans);
X
X#ifdef TRACE
X    dptx();
X    dpdread();
X#endif
X}
X
X#ifdef TRACE
X
Xstatic void
Xdptx()
X{
X    int i,st;
X
X    for (i=0; i<cnntx; ++i) {
X	printf("ntx on %s from %u to %u\n",
X	     namenont(ntxtab[i].nont),ntxtab[i].from,ntxtab[i].to);
X    }
X}
X
Xstatic void
Xdpdread()
X{
X    int i,j;
X
X    for (j=0; j<cnstate; ++j) {
X	printf("state %u dread ",j);
X	for (i=0; i<sizebit(cntok) ; ++i) {
X	    printf("%04x",dread[j][i]);
X	}
X	printf("  ");
X	for (i=0; i<cntok; ++i) {
X	    if (isbit(dread[j],i)) {
X		printf("%s ",nametok(i));
X	    }
X	}
X	printf("\n");
X    }
X}
X
X#endif
X
END_OF_FILE
if test 2613 -ne `wc -c <'yardtx.c'`; then
    echo shar: \"'yardtx.c'\" unpacked with wrong size!
fi
# end of 'yardtx.c'
fi
if test -f 'yaread.c' ; then
  echo shar: Will not clobber existing file \"'yaread.c'\"
else
echo shar: Extracting \"'yaread.c'\" \( 4025 characters \)
sed "s/^X//" >'yaread.c' <<'END_OF_FILE'
X/* Yaread.c	29-Oct-86	Read in files for phase 2 */
X/* 25-Jul-87 IBM */
X/* 30-Nov-88 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/* Defines:	rdstr()		rdsym()		rdtok()
X		rdnont()	rdrule()	[dump() - TRACE]
X*/
X
X/* 30-Oct-86	Only read in cnstr chars in rdstr() because when using */
X/*		getc() (rather than agetc()) feof() doesn't detect CPMEOF */
X/*		(ctrl-Z) and hence was reading in beyond the allocated space */
X/*		(Can't use agetc() because it ignores '\r' and hence screws */
X/*		up the offsets into the table !!! */
X/* 09-Jul-89	The last comment is probably of historical significance only */
X/*		now that rdstrch() is used & implementation defined but is */
X/*		a warning to future fiddlers */
X
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xvoid
Xrdstr()
X{
X    int i;
X    char *p;
X
X    message("rdstr:");
X
X    fstring=xopen(nstring,"rb");	/* Read string file */
X    cnstr=getw(fstring);
X    p=strarea=xalloc(cnstr);
X    for (i=0; i<cnstr; ++i) {
X	*p++=rdstrch(fstring);
X    }
X    xclose(fstring,nstring);
X}
X
Xvoid
Xrdsym()
X{
X    void rdtok(),rdnont();
X
X    message("rdsym:");
X
X    fsymbol=xopen(nsymbol,"rb");	/* Read symbols */
X
X    cntok=getw(fsymbol);
X    cnnont=getw(fsymbol);
X    bstok=getw(fsymbol);
X    bsnont=getw(fsymbol);
X
X    rdtok();
X    rdnont();
X
X    xclose(fsymbol,nsymbol);
X}
X
Xvoid
Xrdtok()
X{
X    int i;
X
X    tokstr=(int *)xalloc(cntok*sizeof(int));
X#ifdef FULL
X    toknum=(int *)xalloc(cntok*sizeof(int));
X    tokprec=(int *)xalloc(cntok*sizeof(int));
X    tokassoc=(int *)xalloc(cntok*sizeof(int));
X#endif
X    for (i=0; i < cntok; ++i) {
X	tokstr[i]=getw(fsymbol);
X#ifdef FULL
X	toknum[i]=getw(fsymbol);
X	tokprec[i]=getw(fsymbol);
X	tokassoc[i]=getw(fsymbol);
X#else
X	(void)getw(fsymbol);
X	(void)getw(fsymbol);
X	(void)getw(fsymbol);
X#endif
X    }
X}
X
Xvoid
Xrdnont()
X{
X    int i;
X
X    nontstr=(int *)xalloc(cnnont*sizeof(int));
X    nontrule=(int *)xalloc((cnnont+1)*sizeof(int));	/* NB. plus one */
X
X    for (i=0; i < cnnont; ++i) {
X	nontstr[i]=getw(fsymbol);
X	nontrule[i]=getw(fsymbol);
X    }
X}
X
Xvoid
Xrdrule()
X{
X    int i;
X
X    message("rdrule:");
X
X    frule=xopen(nrule,"rb");		/* Read rules */
X
X    cnrule=getw(frule);
X    cntok=getw(frule);			/* cntok gives offset for nont seq */
X    start=getw(frule);			/* seq number of start nont */
X
X    nontrule[cnnont]=cnrule;		/* Note dummy entry to prevent */
X					/* special case testing */
X
X    rulesym=(int *)xalloc(cnrule*sizeof(int));
X#ifdef FULL
X    ruleseq=(int *)xalloc(cnrule*sizeof(int));
X    ruleprec=(int *)xalloc(cnrule*sizeof(int));
X#endif
X    rulerhs=(int *)xalloc((cnrule+1)*sizeof(int));	/* NB. plus one */
X
X    for (i=0; i<cnrule; ++i) {
X	rulesym[i]=getw(frule);
X#ifdef FULL
X	ruleseq[i]=getw(frule);
X	ruleprec[i]=getw(frule);
X#else
X	(void)getw(frule);
X	(void)getw(frule);
X#endif
X	rulerhs[i]=getw(frule);
X    }
X    xclose(frule,nrule);
X
X    frhs=xopen(nrhs,"rb");
X    cnrhs=getw(frhs);
X    rulerhs[cnrule]=cnrhs;			/* Note dummy entry */
X    rhs=(int *)xalloc(cnrhs*sizeof(int));
X    for (i=0; i<cnrhs; ++i) {
X	rhs[i]=getw(frhs);
X    }
X    xclose(frhs,nrhs);
X}
X
X#ifdef TRACE
X
Xvoid
Xdump()
X{
X    int i,j,r;
X
X    for (i=0; i<cntok; ++i) {
X#ifdef FULL
X	printf("token:<%s> assoc:%u prec:%u toknum:%u\n",
X		nametok(i),tokassoc[i],tokprec[i],toknum[i]);
X#else
X	printf("token:<%s>\n",nametok(i));
X#endif
X    }
X
X    for (i=0; i<cnnont; ++i) {
X	for (r=nontrule[i]; r < nontrule[i+1]; ++r) {
X#ifdef FULL
X	    printf("prec:%u seq:%u\t(%u)%s : ",
X		ruleprec[r],ruleseq[r],i+bsnont,
X		namenont(i));
X#else
X	    printf("%s : ",namenont(i));
X#endif
X	    for (j=rulerhs[r]; j < rulerhs[r+1]; ++j) {
X		printf("%s ",namesym(rhs[j]));
X	    }
X	    printf("\n");
X	}
X    }
X
X    printf("start is <%s>\n",namesym(start));
X
X    printf("%u tokens, %u nonterminals, %u rules, %u rhs symbols\n",
X	cntok,cnnont,cnrule,cnrhs);
X    printf("non-literal token base=%u and nonterminal base=%u\n",
X	bstok,bsnont);
X}
X
X#endif /* TRACE */
X
END_OF_FILE
if test 4025 -ne `wc -c <'yaread.c'`; then
    echo shar: \"'yaread.c'\" unpacked with wrong size!
fi
# end of 'yaread.c'
fi
if test -f 'yareln.c' ; then
  echo shar: Will not clobber existing file \"'yareln.c'\"
else
echo shar: Extracting \"'yareln.c'\" \( 7000 characters \)
sed "s/^X//" >'yareln.c' <<'END_OF_FILE'
X/* Yareln.c	14-Nov-86	Make include and lookback relations */
X/* 25-Jul-87 IBM */
X/* 25-Mar-88 VAXVMS */
X/* 09-Jul-89 ZTC*/
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	mkreln()
X
X	Statics:	addpath()	freepath()	cpsreln()
X			addincl()	findend()	finish()
X			valntx()	valincon()
X			[dpincl(),dplback() - TRACE]
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xtypedef struct path {
X    struct path *next;
X    int hdntx;			/* Ntx from head of path (ie. hdst,rule nont)*/
X    int hdst;			/* State at head of path */
X    int tost;			/* Current transition is to this state */
X} PATH;
X
Xstatic PATH *path;
X
Xvoid
Xmkreln()
X{
X    void addpath(),freepath();
X    void dplback(),dpincl();
X    void addincl(),finish();
X    void cpsreln();
X    int findend(),valntx();
X    int i,j,n,r,nont,st,nmax,sym,from,to,rule,lastrule,dposn,nullposn;
X    BITSTR *l;
X    PATH *p;
X
X    message("mkreln:");
X
X    incl=(BITSTR **)xalloc(cnntx*sizeof(BITSTR *));
X    for (i=0; i <cnntx; ++i) {
X	incl[i]=alcbit(cnntx);
X	zerobit(incl[i],cnntx);
X    }
X    lback=(BITSTR **)xalloc(cnincon*sizeof(BITSTR *));
X    for (i=0; i <cnincon; ++i) {
X	lback[i]=alcbit(cnntx);
X	zerobit(lback[i],cnntx);
X
X	/* Spelling of transitions detects lookback relation only if */
X	/* there is a transition, and misses the case when the complete */
X	/* item is EMPTY (and hence no transitions); so we initialize lback */
X	/* when	1. same state 2. same nont 3. incon complete item is empty */
X
X	r=irule[i];
X	trace(("mkreln: incon %d rule %d\n",i,r));
X	if (rulerhs[r] == rulerhs[r+1]) {	/* Empty */
X	    nont=valnont(rulesym[r]);
X	    st=ist[i];
X	    l=lback[i];
X	    trace(("mkreln: empty st %d nont <%s> lback at %04x\n",
X		st,namenont(nont),l));
X	    for (n=0; n < cnntx; ++n) {
X		if (st == ntxtab[n].from && nont == ntxtab[n].nont) {
X		    trace(("mkreln: set lback ntx %d\n",n));
X		    setbit(l,n);
X		}
X	    }
X	}
X    }
X
X    ftr2=xopen(ntr2,"rb");
X
X    lastrule=-1;			/* For first time through */
X					/* Don't finish off rule -1 ! */
X    path=NULL;
X
X    for (j=0; j<cnrtx; ++j) {		/* Transitions sorted by rule/dposn */
X	sym=getw(ftr2);
X	from=getw(ftr2);
X	to=getw(ftr2);
X	rule=getw(ftr2);
X	dposn=getw(ftr2);
X	trace(("mkreln: sym=%s\tfrom=%u (rule=%u dposn %u) to=%u\n",
X		namesym(sym),from,rule,dposn,to));
X	if (rule != lastrule) {
X	    trace(("mkreln: different rule\n"));
X	    finish(lastrule);
X	    nullposn=findend(rule);
X	    freepath(&path);			/* Start new rule */
X	    lastrule=rule;
X	}
X	if (dposn == 1) {		/* For all tx at beginning of rule */
X	    trace(("mkreln: at beginning\n"));
X	    addpath(&path,valntx(from,valnont(rulesym[rule])),from,from);
X	}
X
X	for (p=path; p; p=p->next) {		/* Follow transition */
X	    trace(("mkreln: test tost=%u from=%u\n",p->tost,from));
X	    if (p->tost == from) {		/* Converge ALL entries */
X		trace(("mkreln: make tost %u\n",to));
X		p->tost=to;			/* Advance transition */
X		if (dposn >= nullposn) {	/* Is rest of rule nullable */
X		    addincl(from,sym,p);	/* Add to includes list */
X		}
X 	    }
X	}
X    }
X
X    finish(rule);			/* Finish the last rule */
X    freepath(&path);
X
X    xclose(ftr2,ntr2);
X
X#ifdef TRACE
X    dpincl();
X    dplback();
X#endif
X#ifdef COMPRESS
X    cpsreln(incl,cnntx,cnntx);
X    cpsreln(lback,cnincon,cnntx);
X#ifdef TRACE
X    dpincl();
X    dplback();
X#endif
X#endif
X}
X
Xstatic void
Xaddpath(apath,hdntx,hdst,tost)		/* Add a new spelling path */
XPATH **apath;
Xint hdntx;
Xint hdst;
Xint tost;
X {
X    PATH *p;
X
X    p=(PATH *)xalloc(sizeof(PATH));
X    p->hdntx=hdntx;
X    p->hdst=hdst;
X    p->tost=tost;
X    p->next= *apath;			/* "= *" avoids old assignment op */
X    *apath=p;
X}
X
Xstatic void
Xfreepath(apath)				/* Free all paths */
XPATH **apath;
X{
X    PATH *p,*p2;
X
X    p= *apath;				/* "= *" avoids old assignment op */
X    while (p) {
X	p2=p->next;
X	xfree((char *)p);
X	p=p2;
X    }
X    *apath=NULL;
X}
X
Xstatic void				/* Compress relations */
Xcpsreln(array,size,width)
XBITSTR **array;				/* array of bit vectors */
Xint size;				/* length of array */
Xint width;				/* length of bit vector */
X{
X    int i,n;
X
X    message("cpsreln:");
X
X    for (n=0; n<size; ++n) {
X	trace(("cpsreln: major %u\n",n));
X	for (i=0; i<n; ++i) {
X	    trace(("cpsreln: minor %u (%04x cf %04x)\n",
X		i,array[n],array[i]));
X	    if (eqbit(array[n],array[i],width)) {
X		trace(("cpsreln:equal\n"));
X		xfree((char *)array[n]);
X		array[n]=array[i];
X		break;
X	    }
X	}
X    }
X}
X
Xstatic void				/* Add head ntx to includes of ntx */
Xaddincl(from,sym,p)
Xint from;				/* List ntx from state */
Xint sym;				/* List ntx symbol */
XPATH *p;				/* Table index of head ntx to add */
X{
X    int ntx;
X
X    if (isnont(sym)) {
X	ntx=valntx(from,valnont(sym));
X	trace(("addincl: add %u to include of %u\n",
X		p->hdntx,ntx));
X	if (ntx != -1 && p->hdntx != -1) {
X	    setbit(incl[ntx],p->hdntx);
X	}
X    }
X}
X
Xstatic int
Xfindend(rule)
Xint rule;
X{
X    int s,nullposn;
X
X    for (nullposn=lngrule(rule); nullposn > 0; --nullposn) {
X	s=rhs[rulerhs[rule]+nullposn-1];
X	if (istok(s) || !isbit(nullable,valnont(s))) {
X	    break;
X	}
X    }
X    trace(("mkreln: rule %u nullposn %u\n",rule,nullposn));
X    return nullposn;
X
X/*	    nullposn is dposn AFTER which rest of rule is nullable
X	    ie. symbol at dposn itself is not nullable
X	    eg.
X		- no nullable symbols - nullposn=lngrule - ie. the last posn
X		- all nullable symbols - nullposn=0
X		- empty rule - nullposn=0
X*/
X}
X
Xstatic void
Xfinish(r)
Xint r;					/* Rule */
X{
X    int valincon();
X    int k;
X    PATH *p;
X
X    for (p=path; p; p=p->next) {
X	trace(("finish: add lookback ntx %u\n",p->hdntx));
X	if (p->hdntx != -1) {
X	    trace(("finish: to incon st %u rule %u\n",
X		p->tost,r));
X	    if ((k=valincon(p->tost,r)) != -1) {
X		setbit(lback[k],p->hdntx);
X	    }
X	}
X    }
X}
X
Xstatic int
Xvalntx(st,nont)
Xint st,nont;
X{
X    int i;
X
X    trace(("valntx: from st %u on %s\n",st,namenont(nont)));
X    for (i=0; i<cnntx; ++i) {
X	if (ntxtab[i].from == st && ntxtab[i].nont == nont) {
X	    return i;
X	}
X    }
X    trace(("valntx: can't find\n"));
X    return -1;
X}
X
Xstatic int
Xvalincon(st,rule)
Xint st,rule;
X{
X    int i;
X
X    trace(("valincon: st %u rule %u\n",st,rule));
X    for (i=0; i<cnincon; ++i) {
X	if (ist[i] == st && irule[i] == rule) {
X	    return i;
X	}
X    }
X    trace(("valincon: can't find\n"));
X    return -1;
X}
X
X#ifdef TRACE
X
Xstatic void
Xdpincl()
X{
X    int i,n;
X
X    for (i=0; i < cnntx; ++i) {			/* For all ntx */
X	printf("%u:(from %u to %u on %s)\tincludes(%04x)=> ",
X		i,ntxtab[i].from,ntxtab[i].to,namenont(ntxtab[i].nont),
X		incl[i]);
X	for (n=0; n<cnntx; ++n) {
X	    if (isbit(incl[i],n)) {
X		printf("%u ",n);
X	    }
X        }
X	printf("\n");
X    }
X}
X
Xstatic void
Xdplback()
X{
X    int i,n;
X
X    for (i=0; i < cnincon; ++i) {	/* For all items */
X	printf("%u:(state %u rule %u)\tlookback(%04x)=> ",
X		i,ist[i],irule[i],lback[i]);
X	for (n=0; n<cnntx; ++n) {
X	    if (isbit(lback[i],n)) {
X		printf("%u ",n);
X	    }
X        }
X	printf("\n");
X    }
X}
X
X#endif
X
END_OF_FILE
if test 7000 -ne `wc -c <'yareln.c'`; then
    echo shar: \"'yareln.c'\" unpacked with wrong size!
fi
# end of 'yareln.c'
fi
if test -f 'yasort.c' ; then
  echo shar: Will not clobber existing file \"'yasort.c'\"
else
echo shar: Extracting \"'yasort.c'\" \( 5293 characters \)
sed "s/^X//" >'yasort.c' <<'END_OF_FILE'
X/* Yasort.c	04-Dec-86	General sort/merge for yacc */
X/* 20-Jul-87 IBM */
X/* 25-Nov-88 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	sort()
X
X	Statics:	makfil()	gname()		itoa()
X			gopen()		gremov()	merge()
X			reheap()	gwrite()	gread()
X
X	Uses:		qsort()
X*/
X
X#include <stdio.h>
X
X#include "yadefs.h"
X
X#define	MERGEORDER	4
X
Xstatic namesize;
Xstatic char *name;
Xstatic char *prefix = "sort";
Xstatic char *suffix = ".$$$";
Xstatic char *namepath;
X
Xstatic char *(*rd)();
Xstatic FILE *(*rop)();
Xstatic void (*rcl)();
Xstatic void (*wr)();
Xstatic FILE *(*wop)();
Xstatic void (*wcl)();
Xstatic int (*cmp)();
X
Xint
Xsort(inname,outname,tmppath,maxptr,prd,prop,prcl,pwr,pwop,pwcl,pcmp)
Xchar *inname,*outname,*tmppath;
Xchar *(*prd)();
XFILE *(*prop)();
Xvoid (*prcl)();
Xvoid (*pwr)();
XFILE *(*pwop)();
Xvoid (*pwcl)();
Xint (*pcmp)();
X{
X    FILE *makfil();
X    int gread();
X    int gsetname();
X    void qsort(),merge(),gwrite(),gopen(),gname(),gremov();
X    int low,high,lim,nlines;
X    FILE *outfil,*infil[MERGEORDER];
X    char **linptr;
X    char *holdbuf;
X
X    message("sort:");
X
X    namepath=tmppath;
X    if (gsetname() == -1) return -1;
X
X    rd=prd;
X    rop=prop;
X    rcl=prcl;
X    wr=pwr;
X    wop=pwop;
X    wcl=pwcl;
X    cmp=pcmp;
X
X    high=0;
X    infil[0]=(*rop)(inname);
X    if ((linptr=(char **)malloc(maxptr*sizeof(char *))) == NULL) {
X	errmsg("sort: out of memory allocating pointer array",ABORT);
X	return -1;
X    }
X    holdbuf=malloc(BUFSIZ);		/* Reserve buffer BEFORE filling mem */
X					/* If no room, just have to use char */
X    while (nlines=gread(linptr,maxptr,infil[0])) {
X	qsort(linptr,nlines,sizeof(char *),cmp);
X	++high;
X	outfil=makfil(high);
X	setbuf(outfil,holdbuf);
X	gwrite(linptr,nlines,outfil);
X	(*wcl)(outfil);
X    }
X    (*rcl)(infil[0]);
X    free(linptr);
X    free(holdbuf);
X
X    for (low=1; low<high; low+=MERGEORDER) {
X	if ((lim=low+MERGEORDER-1) > high) {
X	    lim=high;
X	}
X	gopen(infil,low,lim);
X	++high;
X	outfil=makfil(high);
X	merge(infil,lim-low+1,outfil);
X	(*wcl)(outfil);
X	gremov(infil,low,lim);
X    }
X
X    gname(high);
X    unlink(outname);
X    rename(name,outname);
X    return 0;
X}
X
Xstatic FILE *
Xmakfil(n)
Xint n;
X{
X    void gname();
X
X    trace(("makfil:\n"));
X    gname(n);
X    return (*wop)(name);
X}
X
Xstatic int
Xgsetname()
X{
X    namesize=strlen(namepath)+strlen(prefix)+strlen(suffix)
X	+sizeof(int)*3+1;
X    if ((name=malloc(namesize)) == NULL) {
X	errmsg("sort: out of memory allocating name buffer",ABORT);
X	return -1;
X    }
X    trace(("gsetname: length %d\n",namesize));
X    return 0;
X}
X
Xstatic void
Xgname(n)
Xint n;
X{
X    char *itoa();
X
X    strcpy(name,namepath);
X    strcat(name,prefix);
X    (void)itoa(n,name+strlen(name),10);
X    strcat(name,suffix);
X    trace(("gname: <%s>\n",name));
X}
X
Xstatic void			/* Open group of files low ... lim (incl) */
Xgopen(infil,low,lim)
XFILE **infil;
Xint low;
Xint lim;
X{
X    int i;
X
X    trace(("gopen:\n"));
X
X    for (i=0; i<lim-low+1; ++i) {
X	gname(low+i);
X	infil[i]=(*rop)(name);
X    }
X}
X
Xstatic void
Xgremov(infil,low,lim)
XFILE **infil;
Xint low;
Xint lim;
X{
X    int i;
X
X    trace(("gremov:\n"));
X
X    for (i=0; i<lim-low+1; ++i) {
X	(*rcl)(infil[i]);
X	gname(low+i);
X	unlink(name);
X    }
X}
X
Xstatic void
Xmerge(infil,nfiles,outfil)
XFILE **infil;
Xint nfiles;
XFILE *outfil;
X{
X    void reheap();
X    int i,base;
X    char **linptr,*p;
X    FILE **linfil;
X
X    trace(("merge:\n"));
X
X    linptr=(char **)malloc(nfiles*sizeof(char *));
X    linfil=(FILE **)malloc(nfiles*sizeof(FILE *));
X    base=nfiles;
X    for (i=0; i<nfiles; ++i) {
X	if (p=(*rd)(infil[i])) {			/* !eof */
X	    linptr[--base]=p;
X	    linfil[base]=infil[i];
X	    reheap(linptr+base,linfil+base,nfiles-base);
X	}
X    }
X
X    while (base < nfiles) {
X	(*wr)(linptr[base],outfil);
X	if ((linptr[base]=(*rd)(linfil[base])) == NULL) {	/* eof */
X	    ++base;
X	}
X	reheap(linptr+base,linfil+base,nfiles-base);
X    }
X    free(linptr);
X    free(linfil);
X}
X
Xstatic void
Xreheap(linptr,linfil,nf)
Xchar **linptr;
XFILE **linfil;
X{
X    int i,j;
X    char *tptr;
X    FILE *tfil;
X
X#ifdef HEAPTRACE
X    for (i=0; i<nf; ++i) {
X	printf("reheap: start %u <%s>\n",i,linptr[i]);
X    }
X#endif
X    for (i=1; 2*i <= nf; i=j) {
X	j=2*i;
X#ifdef HEAPTRACE
X	printf("reheap: i=%u j=%u\n",i,j);
X#endif
X	if (j < nf) {			/* Are two children */
X	    if ((*cmp)(linptr+j-1,linptr+j) > 0) {
X		++j;
X#ifdef HEAPTRACE
X		printf("reheap: 2nd child smaller j=%u\n",j);
X#endif
X	    }
X	}
X	if ((*cmp)(linptr+i-1,linptr+j-1) <= 0) {
X#ifdef HEAPTRACE
X	    printf("reheap: parent <= child - done\n");
X#endif
X	    break;
X	}
X	tptr=linptr[i-1];
X	tfil=linfil[i-1];
X	linptr[i-1]=linptr[j-1];
X	linfil[i-1]=linfil[j-1];
X	linptr[j-1]=tptr;
X	linfil[j-1]=tfil;
X    }
X#ifdef HEAPTRACE
X    for (i=0; i<nf; ++i) {
X	printf("reheap: finish %u <%s>\n",i,linptr[i]);
X    }
X#endif
X}
X
Xstatic void
Xgwrite(linptr,nmax,file)
Xchar **linptr;
Xint nmax;
XFILE *file;
X{
X    int i;
X
X    trace(("gwrite:\n"));
X
X    for (i=0; i<nmax; ++i) {
X	(*wr)(linptr[i],file);
X    }
X}
X
Xstatic int
Xgread(linptr,nmax,file)
Xchar **linptr;
Xint nmax;
XFILE *file;
X{
X    int i;
X
X    trace(("gread:\n"));
X
X    for (i=0; i<nmax; ++i) {
X	if ((linptr[i]=(*rd)(file)) == NULL) {		/* eof or out of mem */
X	    return i;
X	}
X    }
X    return nmax;
X}
X
END_OF_FILE
if test 5293 -ne `wc -c <'yasort.c'`; then
    echo shar: \"'yasort.c'\" unpacked with wrong size!
fi
# end of 'yasort.c'
fi
if test -f 'yasym.c' ; then
  echo shar: Will not clobber existing file \"'yasym.c'\"
else
echo shar: Extracting \"'yasym.c'\" \( 2290 characters \)
sed "s/^X//" >'yasym.c' <<'END_OF_FILE'
X/* Yasym.c   17-Oct-86 		Phase 1 symbol table management routines */
X/* 17-Oct-86 Derived from gsym.c */
X/* 17-Oct-86 Addsym() sets sym->kind to NONE */
X/* 25-Jul-87 IBM */
X/* 09-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	chksym()	fndsym()	addsym()
X			ithash()	fnhash()
X
X	Statics:	hash()
X*/
X
X#include <stdio.h>
X
X#define	PHASE1
X
X#include "yadefs.h"
X
Xstatic SYMBOL **hashtab;		/* Hash tables are */
Xstatic int *hashlength;			/* dynamically allocated */
X
XSYMBOL *chksym(s)			/* find symbol s or add it */
Xchar *s;
X{
X    int h;
X    SYMBOL *p,*fndsym(),*addsym();
X
X    h=hash(s);
X    if ((p=fndsym(s,h)) != NULL)
X	return p;
X    else
X	return addsym(s,h);
X}
X
XSYMBOL *fndsym(s,h)				/* find symbol named s */
Xchar *s;
Xint h;
X{
X    SYMBOL *p;
X    int l;
X
X    p=hashtab[h];
X    l=hashlength[h];
X    while (l-- && p != NULL) {
X	if (!strcmp(s,p->name))
X	    return p;
X	else
X	    p=p->lsym;
X    }
X    return NULL;
X}
X
XSYMBOL *addsym(s,h)				/* add a new symbol named s */
Xchar *s;
Xint h;
X{
X    int l;
X    SYMBOL *p,*p2;
X
X    p=(SYMBOL *) xalloc(sizeof(SYMBOL));	/* type name K&P 8.7 */
X    p->name=xalloc(strlen(s)+1);		/* space for \0 */
X    strcpy(p->name,s);
X
X    p->kind=NONE;
X
X    l=hashlength[h]++;				/* length of chain for h */
X
X    if (l) {					/* are already hash entries */
X	p2=hashtab[h];				/* first entry in hash chain */
X	while (--l) {				/* find last in hash chain */
X	    p2=p2->lsym;
X	}
X	p->lsym=p2->lsym;			/* insert p after p2 */
X	p2->lsym=p;
X    }
X    else {					/* hash table empty at h */
X	hashtab[h]=p;				/* put entry in hash table */
X	p->lsym=shead;				/* insert p at shead */
X	shead=p;
X    }
X
X    return p;
X}
X
Xstatic int hash(s)
Xchar *s;
X{
X    int i;
X
X    i=0;
X    while (*s) {
X	i+=*s++ & HASHMASK;
X	if (*s) i+=(*s++ & HASHMASK)<<HASHIFT;
X    }
X    return i%HASHSIZE;
X}
X
Xvoid ithash()
X{
X    int i;
X
X    shead=NULL;				/* link chain is empty */
X
X    hashtab=(SYMBOL **) xalloc(sizeof(SYMBOL *) * HASHSIZE);
X    hashlength=(int *) xalloc(sizeof(int) * HASHSIZE);
X
X    for (i=0;i<HASHSIZE;i++) {
X	hashtab[i]=NULL;
X	hashlength[i]=0;
X    }
X}
X
Xvoid fnhash()
X{
X    xfree((char *)hashtab);
X    xfree((char *)hashlength);
X}
X
END_OF_FILE
if test 2290 -ne `wc -c <'yasym.c'`; then
    echo shar: \"'yasym.c'\" unpacked with wrong size!
fi
# end of 'yasym.c'
fi
if test -f 'yasystem.h' ; then
  echo shar: Will not clobber existing file \"'yasystem.h'\"
else
echo shar: Extracting \"'yasystem.h'\" \( 2729 characters \)
sed "s/^X//" >'yasystem.h' <<'END_OF_FILE'
X/* yapcdos.h 08-Jul-89 Implementation dependent things for IBM PC DOS */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X#ifdef __ZTC__
X#define SYSTEM	 "PC-DOS ZTC (file)"
X#else
X#define SYSTEM	 "PC-DOS (file)"
X#endif
X
X#define PCDOS
X
X#ifdef __ZTC__
X
X#define STDLIBHEAD	<stdlib.h>	/* define if stdlib.h needed */
X#define	STRINGHEAD	<string.h>	/* define if string.h needed */
X#define	TIMEHEAD	<time.h>	/* define if time.h needed */
X
X#else	/* assume Aztec C */
X
Xchar *malloc();
Xchar *realloc();
X
Xtypedef long clock_t;
X#define	clock()		(0l)
X
X#endif
X
X#ifdef __ZTC__
X#define TTYHEAD	<io.h>		/* define only if isatty() needs io.h */
X#else	/* assume Aztec C */
X#define TTYHEAD	<sgtty.h>	/* define only if isatty() needs sgtty.h */
X#endif
X
X#define	iseofchar(c)	( c == EOF || c == 0x1a )	/* ctrl-Z */
X
X#define BITSTR	unsigned int	/* Type of word used for bit strings */
X
X#define SORTTABLE	3000	/* size of pointer table in txsort() */
X				/* larger -> longer runs */
X#ifdef __ZTC__
X#define	NEEDGETW		/* include x...w() in yautil.c */
X#define	getw(f)		xgetw(f)
X#define	putw(u,f)	xputw(u,f)
X#define	rdstrch(f)	xgetw(f)
X#define	wrstrch(u,f)	xputw(u,f)
X#else	/* assume Aztec C */
X#define	rdstrch(f)	getc(f)
X#define	wrstrch(u,f)	putc(u,f)
X#endif
X
X/* set PATHSEPARATOR to null string "" if paths not implemented */
X#ifndef PATHSEPARATOR
X#define	PATHSEPARATOR	"\\"
X#endif
X
X/* leave TMPENVPATH undefined if compiler can't access environment */
X#ifndef TMPENVPATH			/* if not defined on compile line */
X#define	TMPENVPATH	"TMP"		/* where to find path for temp files */
X#endif
X/* set TMPDEFPATH to null string "" (current directory) if no paths */
X#ifndef TMPDEFPATH			/* if not defined on compile line */
X#define TMPDEFPATH	""		/* path to use if not in environment */
X#endif
X
X/* leave SKELENVPATH undefined if compiler can't access environment */
X#ifndef SKELENVPATH			/* if not defined on compile line */
X#define	SKELENVPATH	"YYSKELETON"	/* where to find path for skeleton */
X#endif
X/* set SKELDEFPATH to null string "" (current directory) if no paths */
X#ifndef SKELDEFPATH			/* if not defined on compile line */
X#define SKELDEFPATH	"c:\\util"	/* path to use if not in environment */
X#endif
X#ifndef SKELDEFNAME			/* if not defined on compile line */
X#define SKELDEFNAME	"yaccpar"	/* path to use if not in environment */
X#endif
X
X#ifndef YTABHDEFNAME			/* if not defined on compile line */
X#define	YTABHDEFNAME	"ytab.h"
X#endif
X#ifndef YTABCDEFNAME			/* if not defined on compile line */
X#define	YTABCDEFNAME	"ytab.c"
X#endif
X#ifndef YOUTDEFNAME			/* if not defined on compile line */
X#define	YOUTDEFNAME	"youtput"
X#endif
END_OF_FILE
if test 2729 -ne `wc -c <'yasystem.h'`; then
    echo shar: \"'yasystem.h'\" unpacked with wrong size!
fi
# end of 'yasystem.h'
fi
if test -f 'yatable.c' ; then
  echo shar: Will not clobber existing file \"'yatable.c'\"
else
echo shar: Extracting \"'yatable.c'\" \( 672 characters \)
sed "s/^X//" >'yatable.c' <<'END_OF_FILE'
X/* Yatable.c	03-Dec-86	Output tables */
X/* 14-May-88 */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	yttable()
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xvoid
Xyttable(file,func,name,size,width)
XFILE *file;
Xint (*func)();
Xchar *name;
Xint size;
Xint width;
X{
X    int i;
X
X    fprintf(file,"yytabelem %s[] = {",name);
X    for (i=0; i<size; ++i) {
X	if (i%width == 0) {
X	    fprintf(file,"\n\t");
X	}
X	fprintf(file,"%d",(*func)(i));
X	if (i < size-1) {
X	    fprintf(file,", ");
X	}
X    }
X    fprintf(file,"\n};\n");
X}
X
END_OF_FILE
if test 672 -ne `wc -c <'yatable.c'`; then
    echo shar: \"'yatable.c'\" unpacked with wrong size!
fi
# end of 'yatable.c'
fi
if test -f 'yatxsort.c' ; then
  echo shar: Will not clobber existing file \"'yatxsort.c'\"
else
echo shar: Extracting \"'yatxsort.c'\" \( 2719 characters \)
sed "s/^X//" >'yatxsort.c' <<'END_OF_FILE'
X/* Yatxsort.c	12-Nov-86	Sort transitions by rule for relations */
X/* 20-Nov-86	Use sort/merge package - terminate trans files with -1 */
X/* 25-Jul-87 IBM */
X/* 25-Mar-88 VAXVMS */
X/* 30-Nov-88 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/* 09-Jul-89	Historical note - I had heaps of trouble with the end-of-file
X		handling when moving between machines. Seems silly I know.
X		Be warned. I hope I haven't messed up the old behaviour under
X		CPM in recent years - I haven't tested it for a while */
X
X/*	Defines:	txsort()
X
X	Statics:	rtxrop()	rtxwop()	rtxrcl()
X			rtxwcl()	rtxrd()		rtxwr()
X			rtxcmp()
X*/
X
X#include <stdio.h>
X
X#define PHASE2
X
X#include "yadefs.h"
X
Xtypedef struct rtx {
X    int sym;
X    int from;
X    int to;
X    int rule;
X    int dposn;
X} RTX;
X
Xvoid
Xtxsort()				/* Sort transitions */
X{
X    int sort();
X    RTX *rtxrd();
X    int rtxcmp();
X    void rtxwr(),rtxrcl(),rtxwcl();
X    FILE *rtxrop(),*rtxwop();
X
X    message("txsort:");
X
X    sort(ntrans,ntr2,g_tmppath,
X	SORTTABLE,rtxrd,rtxrop,rtxrcl,rtxwr,rtxwop,rtxwcl,rtxcmp);
X}
X
Xstatic FILE *
Xrtxrop(name)
Xchar *name;
X{
X    return xopen(name,"rb");
X}
X
Xstatic FILE *
Xrtxwop(name)
Xchar *name;
X{
X    return xopen(name,"wb");
X}
X
Xstatic void
Xrtxrcl(file)
XFILE *file;
X{
X    xclose(file,"???");
X}
X
Xstatic void
Xrtxwcl(file)
XFILE *file;
X{
X    putw(-1,file);
X    xclose(file,"???");
X}
X
Xstatic RTX *
Xrtxrd(file)
XFILE *file;
X{
X    static int outofmem=0;
X    RTX *rtx;
X
X    if (rtx=(RTX *)malloc(sizeof(RTX))) {
X	outofmem=0;
X	if ((rtx->sym=getw(file)) == -1 || feof(file)) {
X	    free(rtx);
X	    rtx=0;
X#ifdef TRACE
X	    printf("rtxrd: eof\n");
X#endif
X	}
X	else {
X	    rtx->from=getw(file);	/* From state */
X	    rtx->to=getw(file);		/* To state */
X	    rtx->rule=getw(file);	/* Rule */
X	    rtx->dposn=getw(file);	/* Distinguished posn (from) */
X#ifdef TRACE
X	    printf("rtxrd: sym=%s\tfrom=%u to=%u rule=%u dposn=%u\n",
X		namesym(rtx->sym),rtx->from,rtx->to,rtx->rule,rtx->dposn);
X#endif
X	}
X    }
X    else {				/* Out of memory */
X	if (outofmem) {			/* Twice in a row */
X	    fputs("rtxrd: out of memory\n",stderr);
X	    exit(1);
X	}
X	outofmem=1;
X    }
X    return rtx;
X}
X
Xstatic void
Xrtxwr(rtx,file)
XRTX *rtx;
XFILE *file;
X{
X    putw(rtx->sym,file);
X    putw(rtx->from,file);
X    putw(rtx->to,file);
X    putw(rtx->rule,file);
X    putw(rtx->dposn,file);
X    free(rtx);
X}
X
Xstatic int
Xrtxcmp(a,b)
XRTX **a,**b;
X{
X    int i;
X
X    if ((i=(*a)->rule-(*b)->rule) == 0) {
X	i=(*a)->dposn-(*b)->dposn;
X    }
X#ifdef TRACE
X    printf("cmprtx: a(%u,%u) - b(%u,%u) = %u\n",(*a)->rule,(*a)->dposn,
X	(*b)->rule,(*b)->dposn,i);
X#endif
X    return i;
X}
X
END_OF_FILE
if test 2719 -ne `wc -c <'yatxsort.c'`; then
    echo shar: \"'yatxsort.c'\" unpacked with wrong size!
fi
# end of 'yatxsort.c'
fi
if test -f 'yautil.c' ; then
  echo shar: Will not clobber existing file \"'yautil.c'\"
else
echo shar: Extracting \"'yautil.c'\" \( 4578 characters \)
sed "s/^X//" >'yautil.c' <<'END_OF_FILE'
X/* Yautil.c	18-Oct-86	Memory, file routines with error handling */
X/* 22-Jul-87 IBM */
X/* 09-Jul-89 ZTC */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X/*	Defines:	[xgetw()	xputw()		itoa()]
X			open()		xopen()		xalloc()
X			xrealloc()	xfree()		message()
X			errmsg()	er2msg()	bug()
X			yyerror()	yyterror()	enquote()
X
X	Uses:		where()
X*/
X
X#include <stdio.h>
X
X#define	PHASE0
X
X#include "yadefs.h"
X
X#ifdef NEEDGETW
X
X#ifndef NOTBINARY	/* is this what they call a double negative ? */
X
Xint
Xxgetw(f)
XFILE *f;
X{
X    int b1,b2;
X
X    if ((b1=getc(f)) == EOF || (b2=getc(f)) == EOF)
X	return EOF;
X    else
X	return ( (b2<<8) | b1 );
X}
X
Xint
Xxputw(u,f)
Xunsigned u;
XFILE *f;
X{
X    if (putc(u & 0xff,f) == EOF || putc((u>>8) & 0xff,f) == EOF)
X	return EOF;
X    else
X	return u;
X}
X
X#else	/* NOTBINARY */
X
X/* horrendous but useful start during new ports ! */
X
Xint
Xxgetw(f)
XFILE *f;
X{
X    unsigned u;
X
X    fscanf(f,"%i",&u);
X    return u;
X}
X
Xint
Xxputw(u,f)
Xunsigned u;
XFILE *f;
X{
X    fprintf(f,"0x%x ",u);
X}
X
X#endif	/* NOTBINARY */
X
X#endif /* NOGETW */
X
X#ifdef NEEDITOA
X
Xchar *
Xitoa(n,s,r)
Xint n;
Xregister char *s;
Xint r;
X{
X    int i;
X
X    if ((i=n/r))
X	s=itoa(i,s,r);
X    *s++=n % r + '0';
X    *s=0;
X    return s;
X}
X
X#endif /* NEEDITOA */
X
X
XFILE *xopen(name,mode)
Xchar *name;
Xchar *mode;
X{
X    FILE *f;
X
X    if ((f=fopen(name,mode)) == NULL) {
X	fputs("Can't open <",stderr);
X	fputs(name,stderr);
X	fputs("> for ",stderr);
X	fputs(mode,stderr);
X	fputs("\n",stderr);
X	exit(1);
X    }
X    return f;
X}
X
Xvoid
Xxclose(f,name)
XFILE *f;
Xchar *name;
X{
X    if (fclose(f) == EOF) {
X	fputs("Can't close <",stderr);
X	fputs(name,stderr);
X	fputs(">\n",stderr);
X	exit(1);
X    }
X}
X
X
Xchar *xalloc(n)					/* Allocate n bytes of store */
Xunsigned n;
X{
X    char *p;
X
X    if (n == 0) {
X	errmsg("xalloc: zero request\n",WARNING);
X	return NULL;
X    }
X    if ((p=malloc(n)) != NULL) {
X	trace(("xalloc: %p bytes %04x\n",p,n));
X	return p;
X    }
X    else
X	errmsg("Xalloc: Out of memory\n",ABORT);
X}
X
Xchar *xrealloc(p,n)			/* Reallocate n bytes of store */
Xchar *p;
Xunsigned n;
X{
X    if (n == 0) {
X	errmsg("xrealloc: zero request\n",WARNING);
X	xfree(p);
X	return NULL;
X    }
X    if ((p=realloc(p,n)) != NULL) {
X	trace(("xrealloc: %p bytes %04x\n",p,n));
X	return p;
X    }
X    else
X	errmsg("xrealloc: Out of memory\n",ABORT);
X}
X
Xvoid
Xxfree(blk)					/* Deallocate block */
Xchar *blk;					/* Size specified in header */
X{
X    free(blk);
X}
X
Xvoid
Xmessage(s)
Xchar *s;
X{
X    if (o_debug) {
X	fputs(s,stdout);
X	fputs("\n",stdout);
X    }
X}
X
Xvoid
Xerrmsg(s,i)
Xchar *s;
Xint i;
X{
X    where(stderr);
X    switch (i) {
X	case WARNING:	fputs(" - Warning - ",stderr);
X			++cnwarning;
X			break;
X	case FATAL:	fputs(" - Fatal - ",stderr);
X			++cnfatal;
X			break;
X	case ABORT:	fputs(" - Abort - ",stderr);
X			break;
X    }
X    fputs(s,stderr);
X    fputs("\n",stderr);
X    if (i == ABORT) {
X	exit(1);
X    }
X}
X
Xvoid
Xer2msg(s1,s2,i)
Xchar *s1,*s2;
Xint i;
X{
X    where(stderr);
X    switch (i) {
X	case WARNING:	fputs(" - Warning - ",stderr);
X			++cnwarning;
X			break;
X	case FATAL:	fputs(" - Fatal - ",stderr);
X			++cnfatal;
X			break;
X	case ABORT:	fputs(" - Abort - ",stderr);
X			break;
X    }
X    fputs("<",stderr);
X    fputs(s1,stderr);
X    fputs("> ",stderr);
X    fputs(s2,stderr);
X    fputs("\n",stderr);
X    if (i == ABORT) {
X	exit(1);
X    }
X}
X
Xvoid
Xbug(s)
Xchar *s;
X{
X    where(stderr);
X    fputs("- Bug - ",stderr);
X    fputs(s,stderr);
X    fputs("\n",stderr);
X    exit(1);
X}
X
Xvoid
Xyyerror(s)
Xchar *s;
X{
X    fprintf(stderr,"- Abort - %s\n",s);
X    exit(1);
X}
X
Xvoid
Xyyterror(token)
Xchar *token;				/* NULL is last in list */
X{
X    static int first=1;			/* expecting 1st in a list */
X
X    if (first) {
X	fprintf(stderr,"- Abort - syntax error");
X    }
X    if (first && token) {
X	fprintf(stderr,", expecting %s",token);
X    }
X    if (!first && token) {
X	fprintf(stderr," or %s",token);
X    }
X    first=0;
X    if (!token) {				/* end of list */
X	fprintf(stderr,"\n");
X	first=1;			/* for next time ... */
X	exit(1);			/* but, alas ... */
X    }
X}
X
Xchar *
Xenquote(old)			/* "stringize" string */
Xchar *old;			/* dealing with escapes and embedded quotes */
X{
X    char *new,*ptr;
X    unsigned lng,index;
X
X    ptr=new=xalloc(lng=(strlen(old)+3));
X    /* includes room for surrounding quotes & trailing \0 */
X
X    *ptr++='"';
X    while (*old) {
X	if (*old == '\\' || *old == '"') {
X	    index=ptr-new;
X	    new=xrealloc(new,++lng);
X	    ptr=new+index;
X	    *ptr++='\\';
X	}
X	*ptr++= *old++;
X    }
X    *ptr++='"';
X    *ptr='\0';
X
X    return new;
X}
X
END_OF_FILE
if test 4578 -ne `wc -c <'yautil.c'`; then
    echo shar: \"'yautil.c'\" unpacked with wrong size!
fi
# end of 'yautil.c'
fi
if test -f 'yavaxvms.h' ; then
  echo shar: Will not clobber existing file \"'yavaxvms.h'\"
else
echo shar: Extracting \"'yavaxvms.h'\" \( 1729 characters \)
sed "s/^X//" >'yavaxvms.h' <<'END_OF_FILE'
X/* 08-Jul-89 not yet tested */
X
X/* Copyright 1987,1988,1989 David A. Clunie. All rights reserved.
X   PO Box 811, Parkville 3052 AUSTRALIA.
X   This program may be freely distributed for non-commercial use. */
X
X#define SYSTEM	 "VAX-VMS"
X#define VAXVMS
X
X/* timer not yet implemented under VMS */
Xtypedef long clock_t;
X#define	clock()		(0l)
X
X#define	unlink(fname)	delete(fname)
X
X#define	iseofchar(c)	( c == EOF )
X
X#define BITSTR	unsigned int	/* Type of word used for bit strings */
X
X#define SORTTABLE	3000	/* size of pointer table in txsort() */
X				/* larger -> longer runs */
X
X
X#define	rdstrch(f)	getc(f)
X#define	wrstrch(u,f)	putc(u,f)
X
X/* set PATHSEPARATOR to null string "" if paths not implemented */
X#ifndef PATHSEPARATOR
X#define	PATHSEPARATOR	""
X#endif
X
X/* leave TMPENVPATH undefined if compiler can't access environment */
X
X/* set TMPDEFPATH to null string "" (current directory) if no paths */
X#ifndef TMPDEFPATH			/* if not defined on compile line */
X#define TMPDEFPATH	""		/* path to use if not in environment */
X#endif
X
X/* leave SKELENVPATH undefined if compiler can't access environment */
X
X/* set SKELDEFPATH to null string "" (current directory) if no paths */
X#ifndef SKELDEFPATH			/* if not defined on compile line */
X#define SKELDEFPATH	""		/* path to use if not in environment */
X#endif
X#ifndef SKELDEFNAME			/* if not defined on compile line */
X#define SKELDEFNAME	"yaccpar"	/* path to use if not in environment */
X#endif
X
X#ifndef YTABHDEFNAME			/* if not defined on compile line */
X#define	YTABHDEFNAME	"ytab.h"
X#endif
X#ifndef YTABCDEFNAME			/* if not defined on compile line */
X#define	YTABCDEFNAME	"ytab.c"
X#endif
X#ifndef YOUTDEFNAME			/* if not defined on compile line */
X#define	YOUTDEFNAME	"youtput"
X#endif
END_OF_FILE
if test 1729 -ne `wc -c <'yavaxvms.h'`; then
    echo shar: \"'yavaxvms.h'\" unpacked with wrong size!
fi
# end of 'yavaxvms.h'
fi
if test -f 'yavers.h' ; then
  echo shar: Will not clobber existing file \"'yavers.h'\"
else
echo shar: Extracting \"'yavers.h'\" \( 58 characters \)
sed "s/^X//" >'yavers.h' <<'END_OF_FILE'
X#define VERSION "yacc version 0.05 July 9, 1989 1:53 AM"
X
END_OF_FILE
if test 58 -ne `wc -c <'yavers.h'`; then
    echo shar: \"'yavers.h'\" unpacked with wrong size!
fi
# end of 'yavers.h'
fi
if test -f 'yyerror.c' ; then
  echo shar: Will not clobber existing file \"'yyerror.c'\"
else
echo shar: Extracting \"'yyerror.c'\" \( 47 characters \)
sed "s/^X//" >'yyerror.c' <<'END_OF_FILE'
Xyyerror(s)
Xchar *s;
X{
X    printf("%s\n",s);
X}
X
END_OF_FILE
if test 47 -ne `wc -c <'yyerror.c'`; then
    echo shar: \"'yyerror.c'\" unpacked with wrong size!
fi
# end of 'yyerror.c'
fi
if test -f 'yymain.c' ; then
  echo shar: Will not clobber existing file \"'yymain.c'\"
else
echo shar: Extracting \"'yymain.c'\" \( 137 characters \)
sed "s/^X//" >'yymain.c' <<'END_OF_FILE'
X/* Yymain.c 14-Jan-87 */
X
X#include <stdio.h>
X
Xmain()
X{
X    return (yyparse());
X}
X
Xyyerror(s)
Xchar *s;
X{
X    fprintf(stderr,"%s\n",s);
X}
X
END_OF_FILE
if test 137 -ne `wc -c <'yymain.c'`; then
    echo shar: \"'yymain.c'\" unpacked with wrong size!
fi
# end of 'yymain.c'
fi
if test -f 'yyterror.c' ; then
  echo shar: Will not clobber existing file \"'yyterror.c'\"
else
echo shar: Extracting \"'yyterror.c'\" \( 336 characters \)
sed "s/^X//" >'yyterror.c' <<'END_OF_FILE'
Xstatic void
Xyyterror(token)
Xchar *token;				/* NULL is last in list */
X{
X    static int first=1;			/* expecting 1st in a list */
X
X    if (first) {
X	printf("syntax error, expecting");
X	first=0;
X    }
X    if (token) {
X	printf(" %s",token);
X    }
X    else {				/* end of list */
X	printf("\n");
X	first=1;			/* for next time ... */
X    }
X}
X
END_OF_FILE
if test 336 -ne `wc -c <'yyterror.c'`; then
    echo shar: \"'yyterror.c'\" unpacked with wrong size!
fi
# end of 'yyterror.c'
fi
if test -f 'yyunion.c' ; then
  echo shar: Will not clobber existing file \"'yyunion.c'\"
else
echo shar: Extracting \"'yyunion.c'\" \( 152 characters \)
sed "s/^X//" >'yyunion.c' <<'END_OF_FILE'
Xvoid
Xyyunion(to,from)
XYYSTYPE *to,*from;
X{
X    char *t,*f;
X    unsigned l;
X
X    for (l=sizeof(YYSTYPE),t=(char *)to,f=(char *)from;l;--l) *t++=*f++;
X}
X
END_OF_FILE
if test 152 -ne `wc -c <'yyunion.c'`; then
    echo shar: \"'yyunion.c'\" unpacked with wrong size!
fi
# end of 'yyunion.c'
fi
echo "End of archive."