[prev in list] [next in list] [prev in thread] [next in thread] 

List:       rpm-cvs
Subject:    [CVS] RPM: rpm-5_4: rpm/rpmdb/ qf.l qf.y
From:       "Jeff Johnson" <jbj () rpm5 ! org>
Date:       2016-05-12 19:06:32
Message-ID: 20160512190632.B7DC65C0CA () rpm5 ! org
[Download RAW message or body]

  RPM Package Manager, CVS Repository
  http://rpm5.org/cvs/
  ____________________________________________________________________________

  Server: rpm5.org                         Name:   Jeff Johnson
  Root:   /v/rpm/cvs                       Email:  jbj@rpm5.org
  Module: rpm                              Date:   12-May-2016 21:06:32
  Branch: rpm-5_4                          Handle: 2016051219063200

  Added files:              (Branch: rpm-5_4)
    rpm/rpmdb               qf.l qf.y

  Log:
    - add to CVS.

  Summary:
    Revision    Changes     Path
    1.1.2.1     +293 -0     rpm/rpmdb/qf.l
    1.1.2.1     +689 -0     rpm/rpmdb/qf.y
  ____________________________________________________________________________

  patch -p0 <<'@@ .'
  Index: rpm/rpmdb/qf.l
  ============================================================================
  $ cvs diff -u -r0 -r1.1.2.1 qf.l
  --- /dev/null	2016-05-12 21:06:26.000000000 +0200
  +++ qf.l	2016-05-12 21:06:32.716768560 +0200
  @@ -0,0 +1,293 @@
  +%option 8bit yylineno noyywrap
  +%option stack
  +
  +%option noyyget_lineno
  +%option noyyget_in
  +%option noyyget_out
  +%option noyyget_text
  +%option noyyget_debug
  +%option noyyget_leng
  +
  +%option noyy_top_state
  +%option noyy_scan_buffer
  +%option noyy_scan_bytes
  +%option noyy_scan_string
  +
  +%option reentrant bison-bridge
  +%option prefix="Qyy"
  +
  +%option extra-type="struct Qcontext_t *"
  +
  +true		[Tt][Rr][Uu][Ee]
  +false		[Ff][Aa][Ll][Ss][Ee]
  +null		[Nn][Uu][Ll][Ll]
  +integer		[-+]?[0-9]+
  +float		([-+]?([0-9]*)?\.[0-9]*([eE][-+]?[0-9]+)?)|([-+]?([0-9]+)(\.[0-9]*)?[eE][-+]?[0-9]+)
  +hexchar		[0-9a-fA-F]{4}
  +ident		[a-zA-Z_]+[0-9a-zA-Z_]*
  +
  +%{
  +    #include <stdlib.h>
  +
  +    #include "qf.h"
  +#define MAX(a, b)   ((a>b)?(a):(b))
  +#define TEXT_BLOCK_SIZE  1024
  +struct Qcontext_t
  +{
  +    char   *value;
  +    size_t  used;
  +    size_t  size;
  +};
  +#ifdef	NOTYET
  +static char * Qdonate(struct Qcontext_t *tok);
  +static void   Qappend(struct Qcontext_t *tok, char *text);
  +#endif
  +
  +    #include "Qgrammar.h"
  +    void yyerror(char *);
  +%}
  +
  +O	[0-7]
  +D	[0-9]
  +NZ	[1-9]
  +L	[a-zA-Z_]
  +A	[a-zA-Z_0-9]
  +H	[a-fA-F0-9]
  +HP	(0[xX])
  +E	([Ee][+-]?{D}+)
  +P	([Pp][+-]?{D}+)
  +FS	(f|F|l|L)
  +IS	(((u|U)(l|L|ll|LL)?)|((l|L|ll|LL)(u|U)?))
  +CP	(u|U|L)
  +SP	(u8|u|U|L)
  +ES	(\\(['"\?\\abfnrtv]|[0-7]{1,3}|x[a-fA-F0-9]+))
  +WS	[ \t\v\n\f\r]
  +
  +%%
  +	/* NOTYET
  +	"/*"		{ comment(); }
  +	 */
  +"#".*		{ /* consume #-comment */ }
  +"//".*		{ /* consume //-comment */ }
  +
  +	/* NOTYET
  +	"auto"					{ return(AUTO); }
  +	"break"					{ return(BREAK); }
  +	"case"					{ return(CASE); }
  +	"char"					{ return(CHAR); }
  +	"const"					{ return(CONST); }
  +	"continue"				{ return(CONTINUE); }
  +	"default"				{ return(DEFAULT); }
  +	"do"					{ return(DO); }
  +	"double"				{ return(DOUBLE); }
  +	"else"					{ return(ELSE); }
  +	"enum"					{ return(ENUM); }
  +	"extern"				{ return(EXTERN); }
  +	"float"					{ return(FLOAT); }
  +	"for"					{ return(FOR); }
  +	"goto"					{ return(GOTO); }
  +	"if"					{ return(IF); }
  +	"inline"				{ return(INLINE); }
  +	"int"					{ return(INT); }
  +	"long"					{ return(LONG); }
  +	"register"				{ return(REGISTER); }
  +	"restrict"				{ return(RESTRICT); }
  +	"return"				{ return(RETURN); }
  +	"short"					{ return(SHORT); }
  +	"signed"				{ return(SIGNED); }
  +	"sizeof"				{ return(SIZEOF); }
  +	"static"				{ return(STATIC); }
  +	"struct"				{ return(STRUCT); }
  +	"switch"				{ return(SWITCH); }
  +	"typedef"				{ return(TYPEDEF); }
  +	"union"					{ return(UNION); }
  +	"unsigned"				{ return(UNSIGNED); }
  +	"void"					{ return(VOID); }
  +	"volatile"				{ return(VOLATILE); }
  +	"while"					{ return(WHILE); }
  +	"_Alignas"                              { return ALIGNAS; }
  +	"_Alignof"                              { return ALIGNOF; }
  +	"_Atomic"                               { return ATOMIC; }
  +	"_Bool"                                 { return BOOL; }
  +	"_Complex"                              { return COMPLEX; }
  +	"_Generic"                              { return GENERIC; }
  +	"_Imaginary"                            { return IMAGINARY; }
  +	"_Noreturn"                             { return NORETURN; }
  +	"_Static_assert"                        { return STATIC_ASSERT; }
  +	"_Thread_local"                         { return THREAD_LOCAL; }
  +	"__func__"                              { return FUNC_NAME; }
  +	 */
  +"else"		{ return ELSE; }
  +"if"		{ return IF; }
  +"while"		{ return WHILE; }
  +
  +"print"		{ return PRINT; }
  +
  +	/* NOTYET
  +	{L}{A}*					{ return check_type(); }
  +	 */
  +
  +[a-z]		{ yylval->sIndex = *yytext - 'a'; return VARIABLE; }
  +
  +{HP}{H}+{IS}?	{ yylval->I = atoll(yytext); return I_CONSTANT; }
  +{NZ}{D}*{IS}?	{ yylval->I = atoll(yytext); return I_CONSTANT; }
  +"0"{O}*{IS}?	{ yylval->I = atoll(yytext); return I_CONSTANT; }
  +	/* NOTNOW
  +	0		{ yylval->I = atoll(yytext); return I_CONSTANT; }
  +	[1-9][0-9]*	{ yylval->I = atoll(yytext); return I_CONSTANT; }
  +	 */
  +
  +	/* NOTYET
  +	{CP}?"'"([^'\\\n]|{ES})+"'"		{ return I_CONSTANT; }
  +	 */
  +
  +	/* NOTYET
  +	{D}+{E}{FS}?				{ return F_CONSTANT; }
  +	{D}*"."{D}+{E}?{FS}?			{ return F_CONSTANT; }
  +	{D}+"."{E}?{FS}?			{ return F_CONSTANT; }
  +	{HP}{H}+{P}{FS}?			{ return F_CONSTANT; }
  +	{HP}{H}*"."{H}+{P}{FS}?			{ return F_CONSTANT; }
  +	{HP}{H}+"."{P}{FS}?			{ return F_CONSTANT; }
  +	 */
  +
  +"**"		{ return POW; }
  +
  +	/* NOTYET
  +	({SP}?\"([^"\\\n]|{ES})*\"{WS}*)+	{ return STRING_LITERAL; }
  +	"..."					{ return ELLIPSIS; }
  +	">>="					{ return RIGHT_ASSIGN; }
  +	"<<="					{ return LEFT_ASSIGN; }
  +	"+="					{ return ADD_ASSIGN; }
  +	"-="					{ return SUB_ASSIGN; }
  +	"*="					{ return MUL_ASSIGN; }
  +	"/="					{ return DIV_ASSIGN; }
  +	"%="					{ return MOD_ASSIGN; }
  +	"&="					{ return AND_ASSIGN; }
  +	"^="					{ return XOR_ASSIGN; }
  +	"|="					{ return OR_ASSIGN; }
  +	 */
  +
  +">>"		{ return RSHIFT; }
  +"<<"		{ return LSHIFT; }
  +
  +	/* NOTYET
  +	"++"					{ return INC_OP; }
  +	"--"					{ return DEC_OP; }
  +	"->"					{ return PTR_OP; }
  +	"&&"					{ return AND_OP; }
  +	"||"					{ return OR_OP; }
  +	 */
  +
  +"<="		{ return LE; }
  +">="		{ return GE; }
  +"=="		{ return EQ; }
  +"!="		{ return NE; }
  +
  +("["|"<:")	{ return '['; }
  +("]"|":>")	{ return ']'; }
  +("{"|"<%")	{ return '{'; }
  +("}"|"%>")	{ return '}'; }
  +
  +	/* NOTYET
  +	"("		{ return '('; }
  +	")"		{ return ')'; }
  +	"<"		{ return '<'; }
  +	">"		{ return '>'; }
  +	"&"		{ return '&'; }
  +	"|"		{ return '|'; }
  +	"^"		{ return '^'; }
  +	"?"		{ return '?'; }
  +	":"		{ return ':'; }
  +	"!"		{ return '!'; }
  +	"~"		{ return '~'; }
  +	","		{ return ','; }
  +	"="		{ return '='; }
  +	"."		{ return '.'; }
  +	"*"		{ return '*'; }
  +	"+"		{ return '+'; }
  +	"/"		{ return '/'; }
  +	"%"		{ return '%'; }
  +	";"		{ return ';'; }
  +	"-"		{ return '-'; }
  +	 */
  +[()<>?:&|^!~,=.*+/%;-]	{ return *yytext; }
  +
  +{WS}+		{ /* ignore whitespace */ }
  +
  +.		{ yyerror("Unknown character"); }
  +
  +%%
  +
  +#ifdef	NOTYET
  +int yywrap(void)        /* called at end of input */
  +{
  +    return 1;           /* terminate now */
  +}
  +
  +static void comment(void)
  +{
  +    int c;
  +
  +    while ((c = input()) != 0)
  +	if (c == '*') {
  +	    while ((c = input()) == '*')
  +		;
  +
  +	    if (c == '/')
  +		return;
  +
  +	    if (c == 0)
  +		break;
  +	}
  +    yyerror("unterminated comment");
  +}
  +
  +static int check_type(void)
  +{
  +    switch (sym_type(yytext)) {
  +    case TYPEDEF_NAME:                /* previously defined */
  +	return TYPEDEF_NAME;
  +    case ENUMERATION_CONSTANT:        /* previously defined */
  +	return ENUMERATION_CONSTANT;
  +    default:                          /* includes undefined */
  +	return IDENTIFIER;
  +    }
  +}
  +
  +static void Qappend(struct Qcontext_t *tok, char *text)
  +{
  +    size_t len = strlen(text);
  +    if((len+tok->used+1)>(tok->size))
  +    {
  +        tok->size += MAX(len+1, TEXT_BLOCK_SIZE);
  +        tok->value = realloc(tok->value, tok->size);
  +        tok->value[tok->used] = '\0';
  +    }
  +    strcat(tok->value, text);
  +    tok->used += len;
  +}
  +
  +static char * Qdonate(struct Qcontext_t *tok)
  +{ 
  +    char *str = tok->value;     //transfer to parser
  +    memset(tok, 0, sizeof(struct Qcontext_t));
  +    return str;
  +}
  +#endif
  +
  +void Qparse_flex_init(Qparse_t *x)
  +{
  +    x->flex_extra = calloc(1, sizeof(struct Qcontext_t));
  +    Qyylex_init(&x->flex_scanner);
  +#ifdef	NOTYET
  +    Qyy_scan_string(x->text, x->flex_scanner);
  +#endif
  +    Qyyset_extra(x->flex_extra, x->flex_scanner);
  +}
  +
  +void Qparse_flex_destroy(Qparse_t *x)
  +{
  +    Qyylex_destroy(x->flex_scanner);
  +    free(x->flex_extra);
  +    x->flex_extra = NULL;
  +}
  @@ .
  patch -p0 <<'@@ .'
  Index: rpm/rpmdb/qf.y
  ============================================================================
  $ cvs diff -u -r0 -r1.1.2.1 qf.y
  --- /dev/null	2016-05-12 21:06:26.000000000 +0200
  +++ qf.y	2016-05-12 21:06:32.729768607 +0200
  @@ -0,0 +1,689 @@
  +%lex-param	{void * scanner}
  +%parse-param	{struct pass_to_bison *x}
  +
  +%{
  +    #include <stdio.h>
  +    #include <stdlib.h>
  +    #include <stdarg.h>
  +    #include <assert.h>
  +    #include "qf.h"
  +
  +#define	yylex	Qyylex
  +#define scanner  (x->flex_scanner)
  +
  +    /* prototypes */
  +    nodeType *opr(int oper, int nops, ...);
  +    nodeType *id(int i);
  +    nodeType *con(unsigned long long value);
  +    void freeNode(nodeType *p);
  +    long long ex(nodeType *p);
  +    long long sym[26]; /* symbol table */
  +
  +extern int Qyylex ();
  +extern int Qyylex_init ();
  +extern int Qyylex_destroy ();
  +
  +    void yyerror(void *x, char *s);
  +    
  +%}
  +
  +%union {
  +    char *S;
  +    void *v;
  +
  +    unsigned long long I;	/* integer */
  +    double F;
  +
  +    char sIndex; /* symbol table index */
  +    nodeType *nPtr; /* node pointer */
  +};
  +
  +%token <I>	I_CONSTANT
  +%token <F>	F_CONSTANT
  +%token <S>	STRING_LITERAL
  +%token <sIndex> VARIABLE
  +%token WHILE IF PRINT
  +
  +%nonassoc IFX
  +%nonassoc ELSE
  +%left '|'
  +%left '^'
  +%left '&'
  +%left EQ NE
  +%left GE LE '>' '<'
  +%left LSHIFT RSHIFT
  +%left '+' '-'
  +%left '*' '/' '%'
  +%nonassoc UMINUS
  +%right POW
  +%type <nPtr> stmt expr stmt_list 
  +
  +// %token	IDENTIFIER I_CONSTANT F_CONSTANT STRING_LITERAL FUNC_NAME SIZEOF
  +// %token	PTR_OP INC_OP DEC_OP LSHIFT RSHIFT LE GE EQ NE
  +// %token	AND_OP OR_OP MUL_ASSIGN DIV_ASSIGN MOD_ASSIGN ADD_ASSIGN
  +// %token	SUB_ASSIGN LEFT_ASSIGN RIGHT_ASSIGN AND_ASSIGN
  +// %token	XOR_ASSIGN OR_ASSIGN
  +// %token	TYPEDEF_NAME ENUMERATION_CONSTANT
  +// 
  +// %token	TYPEDEF EXTERN STATIC AUTO REGISTER INLINE
  +// %token	CONST RESTRICT VOLATILE
  +// %token	BOOL CHAR SHORT INT LONG SIGNED UNSIGNED FLOAT DOUBLE VOID
  +// %token	COMPLEX IMAGINARY 
  +// %token	STRUCT UNION ENUM ELLIPSIS
  +// 
  +// %token	CASE DEFAULT IF ELSE SWITCH WHILE DO FOR GOTO CONTINUE BREAK RETURN
  +// 
  +// %token	ALIGNAS ALIGNOF ATOMIC GENERIC NORETURN STATIC_ASSERT THREAD_LOCAL
  +// 
  +// %start translation_unit
  +
  +%%
  +
  +program:
  +      function { exit(0); }
  +    ;
  +
  +function:
  +      function stmt { ex($2); freeNode($2); }
  +    | /* NULL */
  +    ;
  +
  +// statement
  +//	: labeled_statement
  +//	| compound_statement
  +//	| expression_statement
  +//	| selection_statement
  +//	| iteration_statement
  +//	| jump_statement
  +//	;
  +//
  +// labeled_statement
  +//	: IDENTIFIER ':' statement
  +//	| CASE constant_expression ':' statement
  +//	| DEFAULT ':' statement
  +//	;
  +// 
  +// compound_statement
  +//	: '{' '}'
  +//	| '{'  block_item_list '}'
  +//	;
  +// 
  +// block_item_list
  +//	: block_item
  +//	| block_item_list block_item
  +//	;
  +// 
  +// block_item
  +//	: declaration
  +//	| statement		{ $$ = $1; }
  +//	;
  +// 
  +// expression_statement
  +//	: ';'			{ $$ = opr(';', 2, NULL, NULL); }
  +//	| expression ';'	{ $$ = $1; }
  +//	;
  +// 
  +// selection_statement
  +//	: IF '(' expression ')' statement ELSE statement	{ $$ = opr(IF, 3, $3, $5, $7); }
  +//	| IF '(' expression ')' statement	{ $$ = opr(IF, 2, $3, $5); }
  +//	| SWITCH '(' expression ')' statement
  +//	;
  +// 
  +// iteration_statement
  +//	: WHILE '(' expression ')' statement	{ $$ = opr(WHILE, 2, $3, $5); }
  +//	| DO statement WHILE '(' expression ')' ';'
  +//	| FOR '(' expression_statement expression_statement ')' statement
  +//	| FOR '(' expression_statement expression_statement expression ')' statement
  +//	| FOR '(' declaration expression_statement ')' statement
  +//	| FOR '(' declaration expression_statement expression ')' statement
  +//	;
  +// 
  +// jump_statement
  +//	: GOTO IDENTIFIER ';'
  +//	| CONTINUE ';'
  +//	| BREAK ';'
  +//	| RETURN ';'
  +//	| RETURN expression ';'
  +//	;
  +
  +stmt:
  +      ';'			{ $$ = opr(';', 2, NULL, NULL); }
  +    | expr ';'			{ $$ = $1; }
  +    | PRINT expr ';'		{ $$ = opr(PRINT, 1, $2); }
  +    | VARIABLE '=' expr ';'	{ $$ = opr('=', 2, id($1), $3); }
  +    | WHILE '(' expr ')' stmt	{ $$ = opr(WHILE, 2, $3, $5); }
  +    | IF '(' expr ')' stmt %prec IFX { $$ = opr(IF, 2, $3, $5); }
  +    | IF '(' expr ')' stmt ELSE stmt { $$ = opr(IF, 3, $3, $5, $7); }
  +    | '{' stmt_list '}'		{ $$ = $2; }
  +    ;
  +
  +stmt_list:
  +      stmt			{ $$ = $1; }
  +    | stmt_list stmt		{ $$ = opr(';', 2, $1, $2); }
  +    ;
  +
  +// primary_expression
  +//	: IDENTIFIER
  +//	| constant
  +//	| string
  +//	| '(' expression ')'
  +//	| generic_selection
  +//	;
  +// 
  +// constant
  +//	: I_CONSTANT		/* includes character_constant */
  +//	| F_CONSTANT
  +//	| ENUMERATION_CONSTANT	/* after it has been defined as such */
  +//	;
  +// 
  +// enumeration_constant		/* before it has been defined as such */
  +//	: IDENTIFIER
  +//	;
  +// 
  +// string
  +//	: STRING_LITERAL
  +//	| FUNC_NAME
  +//	;
  +// 
  +// generic_selection
  +//	: GENERIC '(' assignment_expression ',' generic_assoc_list ')'
  +//	;
  +// 
  +// generic_assoc_list
  +//	: generic_association
  +//	| generic_assoc_list ',' generic_association
  +//	;
  +// 
  +// generic_association
  +//	: type_name ':' assignment_expression
  +//	| DEFAULT ':' assignment_expression
  +//	;
  +// 
  +// postfix_expression
  +//	: primary_expression
  +//	| postfix_expression '[' expression ']'
  +//	| postfix_expression '(' ')'
  +//	| postfix_expression '(' argument_expression_list ')'
  +//	| postfix_expression '.' IDENTIFIER
  +//	| postfix_expression PTR_OP IDENTIFIER
  +//	| postfix_expression INC_OP
  +//	| postfix_expression DEC_OP
  +//	| '(' type_name ')' '{' initializer_list '}'
  +//	| '(' type_name ')' '{' initializer_list ',' '}'
  +//	;
  +// 
  +// argument_expression_list
  +//	: assignment_expression
  +//	| argument_expression_list ',' assignment_expression
  +//	;
  +// 
  +// unary_expression
  +//	: postfix_expression
  +//	| INC_OP unary_expression
  +//	| DEC_OP unary_expression
  +//	| unary_operator cast_expression
  +//	| SIZEOF unary_expression
  +//	| SIZEOF '(' type_name ')'
  +//	| ALIGNOF '(' type_name ')'
  +//	;
  +// 
  +// unary_operator
  +//	: '&'
  +//	| '*'
  +//	| '+'
  +//	| '-'
  +//	| '~'
  +//	| '!'
  +//	;
  +// 
  +// cast_expression
  +//	: unary_expression
  +//	| '(' type_name ')' cast_expression
  +//	;
  +// 
  +// multiplicative_expression
  +//	: cast_expression
  +//	| multiplicative_expression '*' cast_expression	{ $$ = opr('*', 2, $1, $3); }
  +//	| multiplicative_expression '/' cast_expression	{ $$ = opr('/', 2, $1, $3); }
  +//	| multiplicative_expression '%' cast_expression	{ $$ = opr('%', 2, $1, $3); }
  +//	;
  +// 
  +// additive_expression
  +//	: multiplicative_expression
  +//	| additive_expression '+' multiplicative_expression { $$ = opr('+', 2, $1, $3); }
  +//	| additive_expression '-' multiplicative_expression { $$ = opr('-', 2, $1, $3); }
  +//	;
  +// 
  +// shift_expression
  +//	: additive_expression
  +//	| shift_expression LSHIFT additive_expression	{ $$ = opr(LSHIFT, 2, $1, $3); }
  +//	| shift_expression RSHIFT additive_expression	{ $$ = opr(RSHIFT, 2, $1, $3); }
  +//	;
  +// 
  +// relational_expression
  +//	: shift_expression
  +//	| relational_expression '<' shift_expression	{ $$ = opr('<', 2, $1, $3); }
  +//	| relational_expression '>' shift_expression	{ $$ = opr('>', 2, $1, $3); }
  +//	| relational_expression LE shift_expression	{ $$ = opr(LE, 2, $1, $3); }
  +//	| relational_expression GE shift_expression	{ $$ = opr(GE, 2, $1, $3); }
  +//	;
  +// 
  +// equality_expression
  +//	: relational_expression
  +//	| equality_expression EQ relational_expression	{ $$ = opr(EQ, 2, $1, $3); }
  +//	| equality_expression NE relational_expression	{ $$ = opr(NE, 2, $1, $3); }
  +//	;
  +// 
  +// and_expression
  +//	: equality_expression
  +//	| and_expression '&' equality_expression	{ $$ = opr('&', 2, $1, $3); }
  +//	;
  +// 
  +// exclusive_or_expression
  +//	: and_expression
  +//	| exclusive_or_expression '^' and_expression	{ $$ = opr('^', 2, $1, $3); }
  +//	;
  +// 
  +// inclusive_or_expression
  +//	: exclusive_or_expression
  +//	| inclusive_or_expression '|' exclusive_or_expression	{ $$ = opr('|', 2, $1, $3); }
  +//	;
  +// 
  +// logical_and_expression
  +//	: inclusive_or_expression
  +//	| logical_and_expression AND_OP inclusive_or_expression
  +//	;
  +// 
  +// logical_or_expression
  +//	: logical_and_expression
  +//	| logical_or_expression OR_OP logical_and_expression
  +//	;
  +// 
  +// conditional_expression
  +//	: logical_or_expression
  +//	| logical_or_expression '?' expression ':' conditional_expression
  +//	;
  +// 
  +// assignment_expression
  +//	: conditional_expression
  +//	| unary_expression assignment_operator assignment_expression
  +//	;
  +// 
  +// assignment_operator
  +//	: '='
  +//	| MUL_ASSIGN
  +//	| DIV_ASSIGN
  +//	| MOD_ASSIGN
  +//	| ADD_ASSIGN
  +//	| SUB_ASSIGN
  +//	| LEFT_ASSIGN
  +//	| RIGHT_ASSIGN
  +//	| AND_ASSIGN
  +//	| XOR_ASSIGN
  +//	| OR_ASSIGN
  +//	;
  +// 
  +// expression
  +//	: assignment_expression
  +//	| expression ',' assignment_expression
  +//	;
  +// 
  +// constant_expression
  +//	: conditional_expression	/* with constraints */
  +//	;
  +
  +expr:
  +      I_CONSTANT		{ $$ = con($1); }
  +    | VARIABLE			{ $$ = id($1); }
  +    | '-' expr %prec UMINUS	{ $$ = opr(UMINUS, 1, $2); }
  +    | expr '+' expr		{ $$ = opr('+', 2, $1, $3); }
  +    | expr '-' expr		{ $$ = opr('-', 2, $1, $3); }
  +    | expr '*' expr		{ $$ = opr('*', 2, $1, $3); }
  +    | expr '/' expr		{ $$ = opr('/', 2, $1, $3); }
  +    | expr '%' expr		{ $$ = opr('%', 2, $1, $3); }
  +    | expr '&' expr		{ $$ = opr('&', 2, $1, $3); }
  +    | expr '|' expr		{ $$ = opr('|', 2, $1, $3); }
  +    | expr '^' expr		{ $$ = opr('^', 2, $1, $3); }
  +    | expr LSHIFT expr		{ $$ = opr(LSHIFT, 2, $1, $3); }
  +    | expr RSHIFT expr		{ $$ = opr(RSHIFT, 2, $1, $3); }
  +    | expr POW expr		{ $$ = opr(POW, 2, $1, $3); }
  +    | expr '<' expr		{ $$ = opr('<', 2, $1, $3); }
  +    | expr '>' expr		{ $$ = opr('>', 2, $1, $3); }
  +    | expr GE expr		{ $$ = opr(GE, 2, $1, $3); }
  +    | expr LE expr		{ $$ = opr(LE, 2, $1, $3); }
  +    | expr NE expr		{ $$ = opr(NE, 2, $1, $3); }
  +    | expr EQ expr		{ $$ = opr(EQ, 2, $1, $3); }
  +    | '(' expr '?' expr ':' expr ')'	{ $$ = opr(IF, 3, $2, $4, $6); }
  +    | '(' expr ')'		{ $$ = $2; }
  +    ; 
  +
  +// declaration
  +//	: declaration_specifiers ';'
  +//	| declaration_specifiers init_declarator_list ';'
  +//	| static_assert_declaration
  +//	;
  +// 
  +// declaration_specifiers
  +//	: storage_class_specifier declaration_specifiers
  +//	| storage_class_specifier
  +//	| type_specifier declaration_specifiers
  +//	| type_specifier
  +//	| type_qualifier declaration_specifiers
  +//	| type_qualifier
  +//	| function_specifier declaration_specifiers
  +//	| function_specifier
  +//	| alignment_specifier declaration_specifiers
  +//	| alignment_specifier
  +//	;
  +// 
  +// init_declarator_list
  +//	: init_declarator
  +//	| init_declarator_list ',' init_declarator
  +//	;
  +// 
  +// init_declarator
  +//	: declarator '=' initializer
  +//	| declarator
  +//	;
  +// 
  +// storage_class_specifier
  +//	: TYPEDEF	/* identifiers must be flagged as TYPEDEF_NAME */
  +//	| EXTERN
  +//	| STATIC
  +//	| THREAD_LOCAL
  +//	| AUTO
  +//	| REGISTER
  +//	;
  +// 
  +// type_specifier
  +//	: VOID
  +//	| CHAR
  +//	| SHORT
  +//	| INT
  +//	| LONG
  +//	| FLOAT
  +//	| DOUBLE
  +//	| SIGNED
  +//	| UNSIGNED
  +//	| BOOL
  +//	| COMPLEX
  +//	| IMAGINARY		/* non-mandated extension */
  +//	| atomic_type_specifier
  +//	| struct_or_union_specifier
  +//	| enum_specifier
  +//	| TYPEDEF_NAME		/* after it has been defined as such */
  +//	;
  +// 
  +// struct_or_union_specifier
  +//	: struct_or_union '{' struct_declaration_list '}'
  +//	| struct_or_union IDENTIFIER '{' struct_declaration_list '}'
  +//	| struct_or_union IDENTIFIER
  +//	;
  +// 
  +// struct_or_union
  +//	: STRUCT
  +//	| UNION
  +//	;
  +// 
  +// struct_declaration_list
  +//	: struct_declaration
  +//	| struct_declaration_list struct_declaration
  +//	;
  +// 
  +// struct_declaration
  +//	: specifier_qualifier_list ';'	/* for anonymous struct/union */
  +//	| specifier_qualifier_list struct_declarator_list ';'
  +//	| static_assert_declaration
  +//	;
  +// 
  +// specifier_qualifier_list
  +//	: type_specifier specifier_qualifier_list
  +//	| type_specifier
  +//	| type_qualifier specifier_qualifier_list
  +//	| type_qualifier
  +//	;
  +// 
  +// struct_declarator_list
  +//	: struct_declarator
  +//	| struct_declarator_list ',' struct_declarator
  +//	;
  +// 
  +// struct_declarator
  +//	: ':' constant_expression
  +//	| declarator ':' constant_expression
  +//	| declarator
  +//	;
  +// 
  +// enum_specifier
  +//	: ENUM '{' enumerator_list '}'
  +//	| ENUM '{' enumerator_list ',' '}'
  +//	| ENUM IDENTIFIER '{' enumerator_list '}'
  +//	| ENUM IDENTIFIER '{' enumerator_list ',' '}'
  +//	| ENUM IDENTIFIER
  +//	;
  +// 
  +// enumerator_list
  +//	: enumerator
  +//	| enumerator_list ',' enumerator
  +//	;
  +// 
  +// enumerator	/* identifiers must be flagged as ENUMERATION_CONSTANT */
  +//	: enumeration_constant '=' constant_expression
  +//	| enumeration_constant
  +//	;
  +// 
  +// atomic_type_specifier
  +//	: ATOMIC '(' type_name ')'
  +//	;
  +// 
  +// type_qualifier
  +//	: CONST
  +//	| RESTRICT
  +//	| VOLATILE
  +//	| ATOMIC
  +//	;
  +// 
  +// function_specifier
  +//	: INLINE
  +//	| NORETURN
  +//	;
  +// 
  +// alignment_specifier
  +//	: ALIGNAS '(' type_name ')'
  +//	| ALIGNAS '(' constant_expression ')'
  +//	;
  +// 
  +// declarator
  +//	: pointer direct_declarator
  +//	| direct_declarator
  +//	;
  +// 
  +// direct_declarator
  +//	: IDENTIFIER
  +//	| '(' declarator ')'
  +//	| direct_declarator '[' ']'
  +//	| direct_declarator '[' '*' ']'
  +//	| direct_declarator '[' STATIC type_qualifier_list assignment_expression ']'
  +//	| direct_declarator '[' STATIC assignment_expression ']'
  +//	| direct_declarator '[' type_qualifier_list '*' ']'
  +//	| direct_declarator '[' type_qualifier_list STATIC assignment_expression ']'
  +//	| direct_declarator '[' type_qualifier_list assignment_expression ']'
  +//	| direct_declarator '[' type_qualifier_list ']'
  +//	| direct_declarator '[' assignment_expression ']'
  +//	| direct_declarator '(' parameter_type_list ')'
  +//	| direct_declarator '(' ')'
  +//	| direct_declarator '(' identifier_list ')'
  +//	;
  +// 
  +// pointer
  +//	: '*' type_qualifier_list pointer
  +//	| '*' type_qualifier_list
  +//	| '*' pointer
  +//	| '*'
  +//	;
  +// 
  +// type_qualifier_list
  +//	: type_qualifier
  +//	| type_qualifier_list type_qualifier
  +//	;
  +// 
  +// 
  +// parameter_type_list
  +//	: parameter_list ',' ELLIPSIS
  +//	| parameter_list
  +//	;
  +//  
  +// parameter_list
  +//	: parameter_declaration
  +//	| parameter_list ',' parameter_declaration
  +//	;
  +//
  +// parameter_declaration
  +//	: declaration_specifiers declarator
  +//	| declaration_specifiers abstract_declarator
  +//	| declaration_specifiers
  +//	;
  +//
  +// identifier_list
  +//	: IDENTIFIER
  +//	| identifier_list ',' IDENTIFIER
  +//	;
  +// 
  +// type_name
  +//	: specifier_qualifier_list abstract_declarator
  +//	| specifier_qualifier_list
  +//	;
  +// 
  +// abstract_declarator
  +//	: pointer direct_abstract_declarator
  +//	| pointer
  +//	| direct_abstract_declarator
  +//	;
  +// 
  +// direct_abstract_declarator
  +//	: '(' abstract_declarator ')'
  +//	| '[' ']'
  +//	| '[' '*' ']'
  +//	| '[' STATIC type_qualifier_list assignment_expression ']'
  +//	| '[' STATIC assignment_expression ']'
  +//	| '[' type_qualifier_list STATIC assignment_expression ']'
  +//	| '[' type_qualifier_list assignment_expression ']'
  +//	| '[' type_qualifier_list ']'
  +//	| '[' assignment_expression ']'
  +//	| direct_abstract_declarator '[' ']'
  +//	| direct_abstract_declarator '[' '*' ']'
  +//	| direct_abstract_declarator '[' STATIC type_qualifier_list assignment_expression ']'
  +//	| direct_abstract_declarator '[' STATIC assignment_expression ']'
  +//	| direct_abstract_declarator '[' type_qualifier_list assignment_expression ']'
  +//	| direct_abstract_declarator '[' type_qualifier_list STATIC assignment_expression ']'
  +//	| direct_abstract_declarator '[' type_qualifier_list ']'
  +//	| direct_abstract_declarator '[' assignment_expression ']'
  +//	| '(' ')'
  +//	| '(' parameter_type_list ')'
  +//	| direct_abstract_declarator '(' ')'
  +//	| direct_abstract_declarator '(' parameter_type_list ')'
  +//	;
  +// 
  +// initializer
  +//	: '{' initializer_list '}'
  +//	| '{' initializer_list ',' '}'
  +//	| assignment_expression
  +//	;
  +// 
  +// initializer_list
  +//	: designation initializer
  +//	| initializer
  +//	| initializer_list ',' designation initializer
  +//	| initializer_list ',' initializer
  +//	;
  +// 
  +// designation
  +//	: designator_list '='
  +//	;
  +// 
  +// designator_list
  +//	: designator
  +//	| designator_list designator
  +//	;
  +// 
  +// designator
  +//	: '[' constant_expression ']'
  +//	| '.' IDENTIFIER
  +//	;
  +// 
  +// static_assert_declaration
  +//	: STATIC_ASSERT '(' constant_expression ',' STRING_LITERAL ')' ';'
  +//	;
  + 
  +%%
  +
  +#define SIZEOF_NODETYPE ((char *)&p->con - (char *)p)
  +
  +nodeType *con(unsigned long long value)
  +{
  +    nodeType * p = malloc(sizeof(*p));
  +assert(p != NULL);
  +    /* copy information */
  +    p->type = typeCon;
  +    p->con.u.I = value;
  +    return p;
  +}
  +
  +nodeType *id(int i)
  +{
  +    nodeType * p = malloc(sizeof(*p));
  +assert(p != NULL);
  +    /* copy information */
  +    p->type = typeId;
  +    p->id.i = i;
  +    return p;
  +} 
  +
  +nodeType *opr(int oper, int nops, ...)
  +{
  +    nodeType * p = malloc(sizeof(*p));
  +    va_list ap;
  +    int i;
  +assert(p != NULL);
  +    p->opr.op = malloc(nops * sizeof(nodeType));
  +assert(p->opr.op != NULL);
  +    /* copy information */
  +    p->type = typeOpr;
  +    p->opr.oper = oper;
  +    p->opr.nops = nops;
  +    va_start(ap, nops);
  +    for (i = 0; i < nops; i++)
  +	p->opr.op[i] = va_arg(ap, nodeType*);
  +    va_end(ap);
  +    return p;
  +}
  +
  +void freeNode(nodeType *p)
  +{
  +    int i;
  +    if (!p) return;
  +    if (p->type == typeOpr) {
  +    for (i = 0; i < p->opr.nops; i++)
  +	freeNode(p->opr.op[i]);
  +	free(p->opr.op);
  +    }
  +    free(p);
  +}
  +
  +void yyerror(void * _x, char *s)
  +{
  +    fflush(stdout);
  +    fprintf(stderr, "*** %s\n", s);
  +}
  +
  +int main(void)
  +{
  +    Qparse_t x;
  +    memset(&x, 0, sizeof(x));
  +
  +    Qparse_flex_init(&x);
  +    yyparse(&x);
  +    Qparse_flex_destroy(&x);
  +
  +    return 0;
  +} 
  @@ .
______________________________________________________________________
RPM Package Manager                                    http://rpm5.org
CVS Sources Repository                                rpm-cvs@rpm5.org
[prev in list] [next in list] [prev in thread] [next in thread] 

Configure | About | News | Add a list | Sponsored by KoreLogic