Skip to content
Snippets Groups Projects
Commit 7d4a6437 authored by James K. Lowden's avatar James K. Lowden :anchor:
Browse files

WIP: introduce new acrc grammar

parent 245a1bfe
No related branches found
No related tags found
No related merge requests found
...@@ -774,9 +774,9 @@ ...@@ -774,9 +774,9 @@
END_IF END_IF
%left THRU %left THRU
%right NOT
%left OR %left OR
%left AND %left AND
%right NOT
%left '<' '>' '=' NE LE GE %left '<' '>' '=' NE LE GE
%left '-' '+' %left '-' '+'
%left '*' '/' %left '*' '/'
...@@ -4644,7 +4644,6 @@ simple_cond: kind_of_name ...@@ -4644,7 +4644,6 @@ simple_cond: kind_of_name
$$->field->parent = field_index($name88->field); $$->field->parent = field_index($name88->field);
parser_relop($$->cond(), parent, eq_op, *$name88); parser_relop($$->cond(), parent, eq_op, *$name88);
} }
| rel_operand
; ;
kind_of_name: expr might_be variable_type kind_of_name: expr might_be variable_type
...@@ -4660,7 +4659,8 @@ kind_of_name: expr might_be variable_type ...@@ -4660,7 +4659,8 @@ kind_of_name: expr might_be variable_type
} }
; ;
bool_expr: bool_expr[lhs] OR and_term[rhs] bool_expr: or_acrc {}
| bool_expr[lhs] OR bool_expr[rhs]
{ {
// cond cond: reduce // cond cond: reduce
// cond value: reduce // cond value: reduce
...@@ -4716,62 +4716,42 @@ bool_expr: bool_expr[lhs] OR and_term[rhs] ...@@ -4716,62 +4716,42 @@ bool_expr: bool_expr[lhs] OR and_term[rhs]
$$.cond->cond(), or_op, rhs->term->cond()); $$.cond->cond(), or_op, rhs->term->cond());
} }
} }
| bool_expr[lhs] OR MIGHT_BE and_term[rhs] | NOT bool_expr
{ {
assert(NOT == $MIGHT_BE); /* $$.cond = $rel_expr.cond; */
if( is_conditional($lhs.cond) && !$lhs.ante.term ) { /* $$.ante = $rel_expr.ante; */
yyerrorv( "error: %s OR NOT %s invalid because " /* $$.abbrs = new acrcs_t; */
"LHS is not a relation condition", /* cbl_refer_t *term($$.cond); */
$lhs.cond->field->name, /* if( is_conditional(term) ) { */
$rhs.cond->field->name ); /* parser_logop( term->cond(), NULL, not_op, term->cond() ); */
YYERROR; /* } else { */
} /* $$.ante.invert = true; */
if( is_conditional($rhs.cond) ) { /* } */
yyerrorv( "error: %s OR NOT %s invalid because RHS is not a value", }
$lhs.cond->field->name, ;
$rhs.cond->field->name );
YYERROR; or_acrc: and_term %prec NOT
} | and_term OR or_abbr
;
or_abbr: rel_abbr
| or_abbr OR rel_abbr
| '(' or_abbr ')'
;
$$ = $lhs;
$rhs.ante.invert = !$rhs.ante.invert;
$rhs.ante.term = $rhs.cond;
auto rhs = apply_acrcs($$.cond, $$.ante, *$$.abbrs, or_op, $rhs.ante);
if( rhs ) {
parser_logop(rhs->term->cond(),
NULL, not_op, rhs->term->cond());
parser_logop($$.cond->cond(),
$$.cond->cond(), or_op, rhs->term->cond());
}
}
| bool_expr[lhs] OR relop and_term[rhs]
{
if( is_conditional($lhs.cond) && !$lhs.ante.term ) {
yyerrorv( "error: %s OR %s %s invalid because "
"LHS is not a relation condition",
$lhs.cond->field->name, keyword_str($relop),
$rhs.cond->field->name );
YYERROR;
}
if( is_conditional($rhs.cond) ) {
yyerrorv( "error: %s OR %s %s invalid because RHS is not a value",
$lhs.cond->field->name, keyword_str($relop),
$rhs.cond->field->name );
YYERROR;
}
$$ = $lhs;
$rhs.ante = acrc_t::make($rhs.cond, relop_of($relop), $rhs.ante.invert);
auto rhs = apply_acrcs($$.cond, $$.ante, *$$.abbrs, or_op, $rhs.ante);
if( rhs ) {
parser_logop($$.cond->cond(),
$$.cond->cond(), or_op, rhs->term->cond());
}
}
| and_term { $$ = $1; }
;
and_term: and_term[lhs] AND rel_expr[rhs] and_term: and_acrc
{
/* $$.cond = $rel_expr.cond; */
/* $$.ante = $rel_expr.ante; */
/* $$.abbrs = new acrcs_t; */
}
| simple_cond
{
$$.ante = {};
$$.cond = $1;
}
| and_term[lhs] AND and_term[rhs]
{ {
// cond cond: reduce // cond cond: reduce
// cond value: reduce // cond value: reduce
...@@ -4797,113 +4777,30 @@ and_term: and_term[lhs] AND rel_expr[rhs] ...@@ -4797,113 +4777,30 @@ and_term: and_term[lhs] AND rel_expr[rhs]
$$.cond->cond(), and_op, rhs->term->cond()); $$.cond->cond(), and_op, rhs->term->cond());
} }
} }
| and_term[lhs] AND NOT rel_expr[rhs] { /* | NOT rel_expr */
// cond NOT cond: reduce /* { */
// cond NOT value: reduce if LHS is relation condition /* $$.cond = $rel_expr.cond; */
// value NOT value: defer /* $$.ante = $rel_expr.ante; */
// value NOT cond: defer /* $$.abbrs = new acrcs_t; */
/* cbl_refer_t *term($$.cond); */
if( !is_conditional($rhs.cond)) { /* if( is_conditional(term) ) { */
if( is_conditional($lhs.cond) && !$lhs.ante.term ) { /* parser_logop( term->cond(), NULL, not_op, term->cond() ); */
yyerrorv( "error: %s AND NOT %s invalid because " /* } else { */
"LHS is not a relation condition", /* $$.ante.invert = true; */
$lhs.cond->field->name, /* } */
$rhs.cond->field->name ); /* } */
YYERROR; ;
}
}
$$ = $lhs;
if( $rhs.ante.is_relation_condition() ) $$.ante = $rhs.ante;
$rhs.ante.invert = !$rhs.ante.invert;
$rhs.ante.term = $rhs.cond;
auto rhs = apply_acrcs($$.cond, $$.ante, *$$.abbrs, and_op, $rhs.ante);
if( rhs ) {
parser_logop(rhs->term->cond(),
NULL, not_op, rhs->term->cond());
parser_logop($$.cond->cond(),
$$.cond->cond(), and_op, rhs->term->cond());
}
if( yydebug && ! $$.abbrs->empty() ) {
warnx("%s AND NOT %s, %zu acrc left",
$$.cond->name(), $rhs.ante.term->name(), $$.abbrs->size() );
}
}
| and_term[lhs] AND MIGHT_BE rel_expr[rhs]
{
// cond NOT cond: reduce
// cond NOT value: reduce if LHS is relation condition
// value NOT value: defer
// value NOT cond: defer
assert(NOT == $MIGHT_BE);
if( !is_conditional($rhs.cond)) {
if( is_conditional($lhs.cond) && !$lhs.ante.term ) {
yyerrorv( "error: %s AND NOT %s invalid because "
"LHS is not a relation condition",
$lhs.cond->field->name,
$rhs.cond->field->name );
YYERROR;
}
}
$$ = $lhs;
$rhs.ante.invert = !$rhs.ante.invert;
$rhs.ante.term = $rhs.cond;
auto rhs = apply_acrcs($$.cond, $$.ante, *$$.abbrs, and_op, $rhs.ante);
if( rhs ) {
parser_logop(rhs->term->cond(),
NULL, not_op, rhs->term->cond());
parser_logop($$.cond->cond(),
$$.cond->cond(), and_op, rhs->term->cond());
}
}
| and_term[lhs] AND relop rel_expr[rhs]
{
if( is_conditional($lhs.cond) && !$lhs.ante.term ) {
yyerrorv( "error: %s AND %s %s invalid because "
"LHS is not a relation condition",
$lhs.cond->field->name, keyword_str($relop),
$rhs.cond->field->name );
YYERROR;
}
if( is_conditional($rhs.cond) ) {
yyerrorv( "error: %s AND %s %s invalid because RHS is not a value",
$lhs.cond->field->name, keyword_str($relop),
$rhs.cond->field->name );
YYERROR;
}
assert( !is_conditional($rhs.cond) );
$$ = $lhs; and_acrc: rel_expr %prec OR
| rel_expr AND and_abbr
;
and_abbr: rel_abbr
| and_abbr AND rel_abbr
| '(' and_abbr ')'
;
$rhs.ante = acrc_t::make($rhs.cond, relop_of($relop), $rhs.ante.invert); rel_abbr: rel_operand
auto rhs = apply_acrcs($$.cond, $$.ante, *$$.abbrs, and_op, $rhs.ante); | relop rel_operand
if( rhs ) {
parser_logop($$.cond->cond(),
$$.cond->cond(), and_op, rhs->term->cond());
}
}
| rel_expr
{
$$.cond = $rel_expr.cond;
$$.ante = $rel_expr.ante;
$$.abbrs = new acrcs_t;
}
| NOT rel_expr
{
$$.cond = $rel_expr.cond;
$$.ante = $rel_expr.ante;
$$.abbrs = new acrcs_t;
cbl_refer_t *term($$.cond);
if( is_conditional(term) ) {
parser_logop( term->cond(), NULL, not_op, term->cond() );
} else {
$$.ante.invert = true;
}
}
; ;
rel_expr: rel_operand[lhs] relop rel_operand[rhs] rel_expr: rel_operand[lhs] relop rel_operand[rhs]
...@@ -4912,11 +4809,6 @@ rel_expr: rel_operand[lhs] relop rel_operand[rhs] ...@@ -4912,11 +4809,6 @@ rel_expr: rel_operand[lhs] relop rel_operand[rhs]
$$.cond = new_reference(new_temporary(FldConditional)); $$.cond = new_reference(new_temporary(FldConditional));
parser_relop($$.cond->cond(), *$lhs, relop_of($relop), *$rhs); parser_relop($$.cond->cond(), *$lhs, relop_of($relop), *$rhs);
} }
| simple_cond
{
$$.ante = {};
$$.cond = $1;
}
; ;
rel_operand: all LITERAL rel_operand: all LITERAL
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment