/[svn]/linuxsampler/trunk/src/scriptvm/parser.y
ViewVC logotype

Annotation of /linuxsampler/trunk/src/scriptvm/parser.y

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3728 - (hide annotations) (download)
Wed Jan 29 13:58:33 2020 UTC (4 years, 3 months ago) by schoenebeck
File size: 68922 byte(s)
NKSP: Reduced code for parsing NKSP variable declarations:

* Use 2 generalized grammar rules with optional components (i.e. optional
  value assignment and optional variable qualifiers) instead of previous
  linear combinations of grammar rules, which also fixes some edge case.

* Bumped version (2.1.1.svn44).

1 schoenebeck 2581 /*
2 schoenebeck 3253 * Copyright (c) 2014-2017 Christian Schoenebeck and Andreas Persson
3 schoenebeck 2581 *
4     * http://www.linuxsampler.org
5     *
6     * This file is part of LinuxSampler and released under the same terms.
7     * See README file for details.
8     */
9 schoenebeck 2888
10     /* Parser for NKSP real-time instrument script language. */
11 schoenebeck 2581
12     %{
13     #define YYERROR_VERBOSE 1
14     #include "parser_shared.h"
15     #include <string>
16     #include <map>
17     using namespace LinuxSampler;
18    
19     void InstrScript_error(YYLTYPE* locp, LinuxSampler::ParserContext* context, const char* err);
20     void InstrScript_warning(YYLTYPE* locp, LinuxSampler::ParserContext* context, const char* txt);
21 schoenebeck 3008 int InstrScript_tnamerr(char* yyres, const char* yystr);
22 schoenebeck 2581 int InstrScript_lex(YYSTYPE* lvalp, YYLTYPE* llocp, void* scanner);
23     #define scanner context->scanner
24 schoenebeck 2888 #define PARSE_ERR(loc,txt) yyerror(&loc, context, txt)
25     #define PARSE_WRN(loc,txt) InstrScript_warning(&loc, context, txt)
26 schoenebeck 3311 #define PARSE_DROP(loc) context->addPreprocessorComment(loc.first_line, loc.last_line, loc.first_column+1, loc.last_column+1);
27 schoenebeck 3008 #define yytnamerr(res,str) InstrScript_tnamerr(res, str)
28 schoenebeck 2581 %}
29    
30     // generate reentrant safe parser
31     %pure-parser
32     %parse-param { LinuxSampler::ParserContext* context }
33     %lex-param { void* scanner }
34     // avoid symbol collision with other (i.e. future) auto generated (f)lex scanners
35 schoenebeck 3052 // (NOTE: "=" is deprecated here with Bison 3.x, however removing it would cause an error with Bison 2.x)
36     %name-prefix="InstrScript_"
37 schoenebeck 2581 %locations
38     %defines
39     %error-verbose
40    
41 schoenebeck 3008 %token <iValue> INTEGER "integer literal"
42 schoenebeck 3573 %token <fValue> REAL "real number literal"
43 schoenebeck 3561 %token <iUnitValue> INTEGER_UNIT "integer literal with unit"
44 schoenebeck 3573 %token <fUnitValue> REAL_UNIT "real number literal with unit"
45 schoenebeck 3008 %token <sValue> STRING "string literal"
46     %token <sValue> IDENTIFIER "function name"
47     %token <sValue> VARIABLE "variable name"
48     %token ON "keyword 'on'"
49     %token END "keyword 'end'"
50     %token INIT "keyword 'init'"
51     %token NOTE "keyword 'note'"
52     %token RELEASE "keyword 'release'"
53     %token CONTROLLER "keyword 'controller'"
54 schoenebeck 3690 %token RPN "keyword 'rpn'"
55     %token NRPN "keyword 'nrpn'"
56 schoenebeck 3008 %token DECLARE "keyword 'declare'"
57     %token ASSIGNMENT "operator ':='"
58     %token CONST_ "keyword 'const'"
59     %token POLYPHONIC "keyword 'polyphonic'"
60     %token WHILE "keyword 'while'"
61 schoenebeck 3260 %token SYNCHRONIZED "keyword 'synchronized'"
62 schoenebeck 3008 %token IF "keyword 'if'"
63     %token ELSE "keyword 'else'"
64     %token SELECT "keyword 'select'"
65     %token CASE "keyword 'case'"
66     %token TO "keyword 'to'"
67     %token OR "operator 'or'"
68     %token AND "operator 'and'"
69     %token NOT "operator 'not'"
70     %token BITWISE_OR "bitwise operator '.or.'"
71     %token BITWISE_AND "bitwise operator '.and.'"
72     %token BITWISE_NOT "bitwise operator '.not.'"
73     %token FUNCTION "keyword 'function'"
74     %token CALL "keyword 'call'"
75     %token MOD "operator 'mod'"
76     %token LE "operator '<='"
77     %token GE "operator '>='"
78     %token END_OF_FILE 0 "end of file"
79 schoenebeck 3259 %token UNKNOWN_CHAR "unknown character"
80 schoenebeck 2581
81 schoenebeck 2951 %type <nEventHandlers> script sections
82     %type <nEventHandler> section eventhandler
83     %type <nStatements> statements opt_statements userfunctioncall
84 schoenebeck 2581 %type <nStatement> statement assignment
85     %type <nFunctionCall> functioncall
86 schoenebeck 3728 %type <nArgs> args opt_arr_assignment
87     %type <nExpression> arg expr logical_or_expr logical_and_expr bitwise_or_expr bitwise_and_expr rel_expr add_expr mul_expr unary_expr concat_expr opt_assignment
88 schoenebeck 2581 %type <nCaseBranch> caseclause
89     %type <nCaseBranches> caseclauses
90 schoenebeck 3728 %type <varQualifier> opt_qualifiers qualifiers qualifier
91 schoenebeck 2581
92     %start script
93    
94     %%
95    
96     script:
97 schoenebeck 2951 sections {
98 schoenebeck 2581 $$ = context->handlers = $1;
99     }
100    
101 schoenebeck 2951 sections:
102     section {
103 schoenebeck 2581 $$ = new EventHandlers();
104 schoenebeck 2951 if ($1) $$->add($1);
105 schoenebeck 2581 }
106 schoenebeck 2951 | sections section {
107 schoenebeck 2581 $$ = $1;
108 schoenebeck 2951 if ($2) $$->add($2);
109 schoenebeck 2581 }
110    
111 schoenebeck 2951 section:
112     function_declaration {
113     $$ = EventHandlerRef();
114     }
115     | eventhandler {
116     $$ = $1;
117     }
118    
119 schoenebeck 2581 eventhandler:
120 schoenebeck 2947 ON NOTE opt_statements END ON {
121 schoenebeck 2581 if (context->onNote)
122 schoenebeck 2888 PARSE_ERR(@2, "Redeclaration of 'note' event handler.");
123 schoenebeck 2581 context->onNote = new OnNote($3);
124     $$ = context->onNote;
125     }
126 schoenebeck 2947 | ON INIT opt_statements END ON {
127 schoenebeck 2581 if (context->onInit)
128 schoenebeck 2888 PARSE_ERR(@2, "Redeclaration of 'init' event handler.");
129 schoenebeck 2581 context->onInit = new OnInit($3);
130     $$ = context->onInit;
131     }
132 schoenebeck 2947 | ON RELEASE opt_statements END ON {
133 schoenebeck 2581 if (context->onRelease)
134 schoenebeck 2888 PARSE_ERR(@2, "Redeclaration of 'release' event handler.");
135 schoenebeck 2581 context->onRelease = new OnRelease($3);
136     $$ = context->onRelease;
137     }
138 schoenebeck 2947 | ON CONTROLLER opt_statements END ON {
139 schoenebeck 2581 if (context->onController)
140 schoenebeck 2888 PARSE_ERR(@2, "Redeclaration of 'controller' event handler.");
141 schoenebeck 2581 context->onController = new OnController($3);
142     $$ = context->onController;
143     }
144 schoenebeck 3690 | ON RPN opt_statements END ON {
145     if (context->onRpn)
146     PARSE_ERR(@2, "Redeclaration of 'rpn' event handler.");
147     context->onRpn = new OnRpn($3);
148     $$ = context->onRpn;
149     }
150     | ON NRPN opt_statements END ON {
151     if (context->onNrpn)
152     PARSE_ERR(@2, "Redeclaration of 'nrpn' event handler.");
153     context->onNrpn = new OnNrpn($3);
154     $$ = context->onNrpn;
155     }
156 schoenebeck 2581
157 schoenebeck 2951 function_declaration:
158     FUNCTION IDENTIFIER opt_statements END FUNCTION {
159     const char* name = $2;
160     if (context->functionProvider->functionByName(name)) {
161     PARSE_ERR(@2, (String("There is already a built-in function with name '") + name + "'.").c_str());
162     } else if (context->userFunctionByName(name)) {
163     PARSE_ERR(@2, (String("There is already a user defined function with name '") + name + "'.").c_str());
164     } else {
165     context->userFnTable[name] = $3;
166     }
167     }
168    
169 schoenebeck 2947 opt_statements:
170 schoenebeck 2911 /* epsilon (empty argument) */ {
171     $$ = new Statements();
172     }
173     | statements {
174     $$ = $1;
175     }
176    
177 schoenebeck 2581 statements:
178     statement {
179     $$ = new Statements();
180     if ($1) {
181     if (!isNoOperation($1)) $$->add($1); // filter out NoOperation statements
182     } else
183 schoenebeck 2888 PARSE_WRN(@1, "Not a statement.");
184 schoenebeck 2581 }
185     | statements statement {
186     $$ = $1;
187     if ($2) {
188     if (!isNoOperation($2)) $$->add($2); // filter out NoOperation statements
189     } else
190 schoenebeck 2888 PARSE_WRN(@2, "Not a statement.");
191 schoenebeck 2581 }
192    
193     statement:
194     functioncall {
195     $$ = $1;
196     }
197 schoenebeck 2951 | userfunctioncall {
198     $$ = $1;
199     }
200 schoenebeck 3728 | DECLARE opt_qualifiers VARIABLE opt_assignment {
201     $$ = new NoOperation; // just as default result value
202     const bool qConst = $2 & QUALIFIER_CONST;
203     const bool qPolyphonic = $2 & QUALIFIER_POLYPHONIC;
204     const char* name = $3;
205     ExpressionRef expr = $4;
206 schoenebeck 2581 //printf("declared var '%s'\n", name);
207 schoenebeck 3728 const ExprType_t declType = exprTypeOfVarName(name);
208 schoenebeck 3573 if (context->variableByName(name)) {
209 schoenebeck 2888 PARSE_ERR(@3, (String("Redeclaration of variable '") + name + "'.").c_str());
210 schoenebeck 3728 } else if (qConst && !expr) {
211     PARSE_ERR(@2, (String("Variable '") + name + "' declared const without value assignment.").c_str());
212     } else if (qConst && qPolyphonic) {
213     PARSE_ERR(@2, (String("Variable '") + name + "' must not be declared both const and polyphonic.").c_str());
214 schoenebeck 2581 } else {
215 schoenebeck 3728 if (!expr) {
216     if (qPolyphonic) {
217     if (name[0] != '$' && name[0] != '~') {
218     PARSE_ERR(@3, "Polyphonic variables must only be declared either as integer or real number type.");
219     } else if (name[0] == '~') {
220     context->vartable[name] = new PolyphonicRealVariable({
221     .ctx = context
222     });
223     } else {
224     context->vartable[name] = new PolyphonicIntVariable({
225     .ctx = context
226     });
227     }
228 schoenebeck 3561 } else {
229 schoenebeck 3728 if (name[0] == '@') {
230     context->vartable[name] = new StringVariable(context);
231     } else if (name[0] == '~') {
232     context->vartable[name] = new RealVariable({
233     .ctx = context
234     });
235     } else if (name[0] == '$') {
236     context->vartable[name] = new IntVariable({
237     .ctx = context
238     });
239     } else if (name[0] == '?') {
240     PARSE_ERR(@3, (String("Real number array variable '") + name + "' declaration requires array size.").c_str());
241 schoenebeck 3573 } else if (name[0] == '%') {
242 schoenebeck 3728 PARSE_ERR(@3, (String("Integer array variable '") + name + "' declaration requires array size.").c_str());
243 schoenebeck 3573 } else {
244 schoenebeck 3728 PARSE_ERR(@3, (String("Variable '") + name + "' declared with unknown type.").c_str());
245 schoenebeck 3573 }
246 schoenebeck 3561 }
247 schoenebeck 2581 } else {
248 schoenebeck 3728 if (qPolyphonic && !isNumber(expr->exprType())) {
249     PARSE_ERR(@3, "Polyphonic variables must only be declared either as integer or real number type.");
250     } else if (expr->exprType() == STRING_EXPR) {
251     if (name[0] != '@')
252     PARSE_WRN(@3, (String("Variable '") + name + "' declared as " + typeStr(declType) + ", string expression assigned though.").c_str());
253     StringExprRef strExpr = expr;
254     String s;
255     if (qConst) {
256     if (strExpr->isConstExpr())
257     s = strExpr->evalStr();
258     else
259     PARSE_ERR(@4, (String("Assignment to const string variable '") + name + "' requires const expression.").c_str());
260     ConstStringVariableRef var = new ConstStringVariable(context, s);
261     context->vartable[name] = var;
262     } else {
263     if (strExpr->isConstExpr()) {
264     s = strExpr->evalStr();
265     StringVariableRef var = new StringVariable(context);
266     context->vartable[name] = var;
267     $$ = new Assignment(var, new StringLiteral(s));
268     } else {
269     StringVariableRef var = new StringVariable(context);
270     context->vartable[name] = var;
271     $$ = new Assignment(var, strExpr);
272 schoenebeck 3573 }
273 schoenebeck 2581 }
274 schoenebeck 3728 } else if (expr->exprType() == REAL_EXPR) {
275     if (name[0] != '~')
276     PARSE_WRN(@3, (String("Variable '") + name + "' declared as " + typeStr(declType) + ", real number expression assigned though.").c_str());
277     RealExprRef realExpr = expr;
278     if (qConst) {
279     if (!realExpr->isConstExpr()) {
280     PARSE_ERR(@4, (String("Assignment to const real number variable '") + name + "' requires const expression.").c_str());
281     }
282     ConstRealVariableRef var = new ConstRealVariable(
283     #if defined(__GNUC__) && !defined(__clang__)
284     (const RealVarDef&) // GCC 8.x requires this cast here (looks like a GCC bug to me); cast would cause an error with clang though
285     #endif
286     {
287     .value = (realExpr->isConstExpr()) ? realExpr->evalReal() : vmfloat(0),
288     .unitFactor = (realExpr->isConstExpr()) ? realExpr->unitFactor() : VM_NO_FACTOR,
289     .unitType = realExpr->unitType(),
290     .isFinal = realExpr->isFinal()
291     });
292     context->vartable[name] = var;
293     } else {
294     RealVariableRef var = new RealVariable({
295     .ctx = context,
296     .unitType = realExpr->unitType(),
297     .isFinal = realExpr->isFinal()
298     });
299     if (realExpr->isConstExpr()) {
300     $$ = new Assignment(var, new RealLiteral({
301     .value = realExpr->evalReal(),
302     .unitFactor = realExpr->unitFactor(),
303     .unitType = realExpr->unitType(),
304     .isFinal = realExpr->isFinal()
305     }));
306     } else {
307     $$ = new Assignment(var, realExpr);
308     }
309     context->vartable[name] = var;
310     }
311     } else if (expr->exprType() == INT_EXPR) {
312     if (name[0] != '$')
313     PARSE_WRN(@3, (String("Variable '") + name + "' declared as " + typeStr(declType) + ", integer expression assigned though.").c_str());
314     IntExprRef intExpr = expr;
315     if (qConst) {
316     if (!intExpr->isConstExpr()) {
317     PARSE_ERR(@4, (String("Assignment to const integer variable '") + name + "' requires const expression.").c_str());
318     }
319     ConstIntVariableRef var = new ConstIntVariable(
320     #if defined(__GNUC__) && !defined(__clang__)
321     (const IntVarDef&) // GCC 8.x requires this cast here (looks like a GCC bug to me); cast would cause an error with clang though
322     #endif
323     {
324     .value = (intExpr->isConstExpr()) ? intExpr->evalInt() : 0,
325     .unitFactor = (intExpr->isConstExpr()) ? intExpr->unitFactor() : VM_NO_FACTOR,
326     .unitType = intExpr->unitType(),
327     .isFinal = intExpr->isFinal()
328     });
329     context->vartable[name] = var;
330     } else {
331     IntVariableRef var = new IntVariable({
332     .ctx = context,
333     .unitType = intExpr->unitType(),
334     .isFinal = intExpr->isFinal()
335     });
336     if (intExpr->isConstExpr()) {
337     $$ = new Assignment(var, new IntLiteral({
338     .value = intExpr->evalInt(),
339     .unitFactor = intExpr->unitFactor(),
340     .unitType = intExpr->unitType(),
341     .isFinal = intExpr->isFinal()
342     }));
343     } else {
344     $$ = new Assignment(var, intExpr);
345     }
346     context->vartable[name] = var;
347     }
348     } else if (expr->exprType() == EMPTY_EXPR) {
349     PARSE_ERR(@4, "Expression does not result in a value.");
350     $$ = new NoOperation;
351     } else if (isArray(expr->exprType())) {
352     PARSE_ERR(@3, (String("Variable '") + name + "' declared as scalar type, array expression assigned though.").c_str());
353     $$ = new NoOperation;
354 schoenebeck 2581 }
355     }
356     }
357     }
358 schoenebeck 3728 | DECLARE opt_qualifiers VARIABLE '[' expr ']' opt_arr_assignment {
359     $$ = new NoOperation; // just as default result value
360     const bool qConst = $2 & QUALIFIER_CONST;
361     const bool qPolyphonic = $2 & QUALIFIER_POLYPHONIC;
362 schoenebeck 3257 const char* name = $3;
363     if (!$5->isConstExpr()) {
364     PARSE_ERR(@5, (String("Array variable '") + name + "' must be declared with constant array size.").c_str());
365     } else if ($5->exprType() != INT_EXPR) {
366     PARSE_ERR(@5, (String("Size of array variable '") + name + "' declared with non integer expression.").c_str());
367     } else if (context->variableByName(name)) {
368     PARSE_ERR(@3, (String("Redeclaration of variable '") + name + "'.").c_str());
369 schoenebeck 3728 } else if (qConst && !$7) {
370     PARSE_ERR(@2, (String("Array variable '") + name + "' declared const without value assignment.").c_str());
371     } else if (qPolyphonic) {
372     PARSE_ERR(@2, (String("Array variable '") + name + "' must not be declared polyphonic.").c_str());
373 schoenebeck 3257 } else {
374     IntExprRef sizeExpr = $5;
375 schoenebeck 3728 ArgsRef args = $7;
376 schoenebeck 3557 vmint size = sizeExpr->evalInt();
377 schoenebeck 3257 if (size <= 0) {
378     PARSE_ERR(@5, (String("Array variable '") + name + "' must be declared with positive array size.").c_str());
379 schoenebeck 3581 } else if (sizeExpr->unitType() || sizeExpr->hasUnitFactorNow()) {
380 schoenebeck 3561 PARSE_ERR(@5, "Units are not allowed as array size.");
381 schoenebeck 3257 } else {
382 schoenebeck 3561 if (sizeExpr->isFinal())
383     PARSE_WRN(@5, "Final operator '!' is meaningless here.");
384 schoenebeck 3728 if (!args) {
385     if (name[0] == '?') {
386     context->vartable[name] = new RealArrayVariable(context, size);
387     } else if (name[0] == '%') {
388     context->vartable[name] = new IntArrayVariable(context, size);
389     } else {
390     PARSE_ERR(@3, (String("Variable '") + name + "' declared as unknown array type: use either '%' or '?' instead of '" + String(name).substr(0,1) + "'.").c_str());
391     }
392 schoenebeck 3573 } else {
393 schoenebeck 3728 if (size <= 0) {
394     PARSE_ERR(@5, (String("Array variable '") + name + "' must be declared with positive array size.").c_str());
395     } else if (args->argsCount() > size) {
396     PARSE_ERR(@7, (String("Array variable '") + name +
397     "' was declared with size " + ToString(size) +
398     " but " + ToString(args->argsCount()) +
399     " values were assigned." ).c_str());
400     } else {
401     ExprType_t declType = EMPTY_EXPR;
402     if (name[0] == '%') {
403     declType = INT_EXPR;
404     } else if (name[0] == '?') {
405     declType = REAL_EXPR;
406     } else if (name[0] == '$') {
407     PARSE_ERR(@3, (String("Variable '") + name + "' declaration ambiguous: Use '%' as name prefix for integer arrays instead of '$'.").c_str());
408     } else if (name[0] == '~') {
409     PARSE_ERR(@3, (String("Variable '") + name + "' declaration ambiguous: Use '?' as name prefix for real number arrays instead of '~'.").c_str());
410     } else {
411     PARSE_ERR(@3, (String("Variable '") + name + "' declared as unknown array type: use either '%' or '?' instead of '" + String(name).substr(0,1) + "'.").c_str());
412 schoenebeck 3573 }
413 schoenebeck 3728 bool argsOK = true;
414     if (declType == EMPTY_EXPR) {
415 schoenebeck 3573 argsOK = false;
416 schoenebeck 3728 } else {
417     for (vmint i = 0; i < args->argsCount(); ++i) {
418     if (args->arg(i)->exprType() != declType) {
419     PARSE_ERR(
420     @7,
421     (String("Array variable '") + name +
422     "' declared with invalid assignment values. Assigned element " +
423     ToString(i+1) + " is not an " + typeStr(declType) + " expression.").c_str()
424     );
425     argsOK = false;
426     break;
427     } else if (qConst && !args->arg(i)->isConstExpr()) {
428     PARSE_ERR(
429     @7,
430     (String("const array variable '") + name +
431     "' must be defined with const values. Assigned element " +
432     ToString(i+1) + " is not a const expression though.").c_str()
433     );
434     argsOK = false;
435     break;
436     } else if (args->arg(i)->asNumber()->unitType()) {
437     PARSE_ERR(
438     @7,
439     (String("Array variable '") + name +
440     "' declared with invalid assignment values. Assigned element " +
441     ToString(i+1) + " contains a unit type, only metric prefixes are allowed for arrays.").c_str()
442     );
443     argsOK = false;
444     break;
445     } else if (args->arg(i)->asNumber()->isFinal()) {
446     PARSE_ERR(
447     @7,
448     (String("Array variable '") + name +
449     "' declared with invalid assignment values. Assigned element " +
450     ToString(i+1) + " declared as 'final' value.").c_str()
451     );
452     argsOK = false;
453     break;
454     }
455     }
456 schoenebeck 3573 }
457 schoenebeck 3728 if (argsOK) {
458     if (declType == REAL_EXPR)
459     context->vartable[name] = new RealArrayVariable(context, size, args, qConst);
460     else
461     context->vartable[name] = new IntArrayVariable(context, size, args, qConst);
462     }
463 schoenebeck 3257 }
464     }
465     }
466     }
467     }
468 schoenebeck 2581 | assignment {
469     $$ = $1;
470     }
471 schoenebeck 2947 | WHILE '(' expr ')' opt_statements END WHILE {
472 schoenebeck 2581 if ($3->exprType() == INT_EXPR) {
473 schoenebeck 3561 IntExprRef expr = $3;
474 schoenebeck 3582 if (expr->asNumber()->unitType() ||
475     expr->asNumber()->hasUnitFactorEver())
476 schoenebeck 3581 PARSE_WRN(@3, "Condition for 'while' loops contains a unit.");
477     else if (expr->isFinal() && expr->isConstExpr())
478 schoenebeck 3561 PARSE_WRN(@3, "Final operator '!' is meaningless here.");
479     $$ = new While(expr, $5);
480 schoenebeck 2581 } else {
481 schoenebeck 2888 PARSE_ERR(@3, "Condition for 'while' loops must be integer expression.");
482 schoenebeck 3581 $$ = new While(new IntLiteral({ .value = 0 }), $5);
483 schoenebeck 2581 }
484     }
485 schoenebeck 3260 | SYNCHRONIZED opt_statements END SYNCHRONIZED {
486     $$ = new SyncBlock($2);
487     }
488 schoenebeck 2947 | IF '(' expr ')' opt_statements ELSE opt_statements END IF {
489 schoenebeck 3561 if ($3->exprType() == INT_EXPR) {
490     IntExprRef expr = $3;
491 schoenebeck 3582 if (expr->asNumber()->unitType() ||
492     expr->asNumber()->hasUnitFactorEver())
493 schoenebeck 3581 PARSE_WRN(@3, "Condition for 'if' contains a unit.");
494     else if (expr->isFinal() && expr->isConstExpr())
495 schoenebeck 3561 PARSE_WRN(@3, "Final operator '!' is meaningless here.");
496     $$ = new If($3, $5, $7);
497     } else {
498     PARSE_ERR(@3, "Condition for 'if' must be integer expression.");
499 schoenebeck 3581 $$ = new If(new IntLiteral({ .value = 0 }), $5, $7);
500 schoenebeck 3561 }
501 schoenebeck 2581 }
502 schoenebeck 2947 | IF '(' expr ')' opt_statements END IF {
503 schoenebeck 3561 if ($3->exprType() == INT_EXPR) {
504     IntExprRef expr = $3;
505 schoenebeck 3582 if (expr->asNumber()->unitType() ||
506     expr->asNumber()->hasUnitFactorEver())
507 schoenebeck 3581 PARSE_WRN(@3, "Condition for 'if' contains a unit.");
508     else if (expr->isFinal() && expr->isConstExpr())
509 schoenebeck 3561 PARSE_WRN(@3, "Final operator '!' is meaningless here.");
510     $$ = new If($3, $5);
511     } else {
512     PARSE_ERR(@3, "Condition for 'if' must be integer expression.");
513 schoenebeck 3581 $$ = new If(new IntLiteral({ .value = 0 }), $5);
514 schoenebeck 3561 }
515 schoenebeck 2581 }
516     | SELECT expr caseclauses END SELECT {
517     if ($2->exprType() == INT_EXPR) {
518 schoenebeck 3561 IntExprRef expr = $2;
519 schoenebeck 3581 if (expr->unitType() || expr->hasUnitFactorEver()) {
520 schoenebeck 3561 PARSE_ERR(@2, "Units are not allowed here.");
521 schoenebeck 3581 $$ = new SelectCase(new IntLiteral({ .value = 0 }), $3);
522 schoenebeck 3561 } else {
523     if (expr->isFinal() && expr->isConstExpr())
524     PARSE_WRN(@2, "Final operator '!' is meaningless here.");
525     $$ = new SelectCase(expr, $3);
526     }
527 schoenebeck 2581 } else {
528 schoenebeck 2888 PARSE_ERR(@2, "Statement 'select' can only by applied to integer expressions.");
529 schoenebeck 3581 $$ = new SelectCase(new IntLiteral({ .value = 0 }), $3);
530 schoenebeck 2581 }
531     }
532    
533     caseclauses:
534     caseclause {
535     $$ = CaseBranches();
536     $$.push_back($1);
537     }
538     | caseclauses caseclause {
539     $$ = $1;
540     $$.push_back($2);
541     }
542    
543     caseclause:
544 schoenebeck 2947 CASE INTEGER opt_statements {
545 schoenebeck 2581 $$ = CaseBranch();
546 schoenebeck 3581 $$.from = new IntLiteral({ .value = $2 });
547 schoenebeck 2581 $$.statements = $3;
548     }
549 schoenebeck 2947 | CASE INTEGER TO INTEGER opt_statements {
550 schoenebeck 2581 $$ = CaseBranch();
551 schoenebeck 3581 $$.from = new IntLiteral({ .value = $2 });
552     $$.to = new IntLiteral({ .value = $4 });
553 schoenebeck 2581 $$.statements = $5;
554     }
555    
556 schoenebeck 2951 userfunctioncall:
557     CALL IDENTIFIER {
558     const char* name = $2;
559     StatementsRef fn = context->userFunctionByName(name);
560     if (context->functionProvider->functionByName(name)) {
561     PARSE_ERR(@1, (String("Keyword 'call' must only be used for user defined functions, not for any built-in function like '") + name + "'.").c_str());
562     $$ = StatementsRef();
563     } else if (!fn) {
564     PARSE_ERR(@2, (String("No user defined function with name '") + name + "'.").c_str());
565     $$ = StatementsRef();
566     } else {
567     $$ = fn;
568     }
569     }
570    
571 schoenebeck 2581 functioncall:
572     IDENTIFIER '(' args ')' {
573     const char* name = $1;
574     //printf("function call of '%s' with args\n", name);
575     ArgsRef args = $3;
576     VMFunction* fn = context->functionProvider->functionByName(name);
577 schoenebeck 2951 if (context->userFunctionByName(name)) {
578     PARSE_ERR(@1, (String("Missing 'call' keyword before user defined function name '") + name + "'.").c_str());
579     $$ = new FunctionCall(name, args, NULL);
580     } else if (!fn) {
581 schoenebeck 2888 PARSE_ERR(@1, (String("No built-in function with name '") + name + "'.").c_str());
582 schoenebeck 2581 $$ = new FunctionCall(name, args, NULL);
583 schoenebeck 3311 } else if (context->functionProvider->isFunctionDisabled(fn,context)) {
584     PARSE_DROP(@$);
585     $$ = new NoFunctionCall;
586 schoenebeck 2581 } else if (args->argsCount() < fn->minRequiredArgs()) {
587 schoenebeck 2888 PARSE_ERR(@3, (String("Built-in function '") + name + "' requires at least " + ToString(fn->minRequiredArgs()) + " arguments.").c_str());
588 schoenebeck 2581 $$ = new FunctionCall(name, args, NULL);
589     } else if (args->argsCount() > fn->maxAllowedArgs()) {
590 schoenebeck 2888 PARSE_ERR(@3, (String("Built-in function '") + name + "' accepts max. " + ToString(fn->maxAllowedArgs()) + " arguments.").c_str());
591 schoenebeck 2581 $$ = new FunctionCall(name, args, NULL);
592     } else {
593     bool argsOK = true;
594 schoenebeck 3557 for (vmint i = 0; i < args->argsCount(); ++i) {
595 schoenebeck 3585 if (!fn->acceptsArgType(i, args->arg(i)->exprType())) {
596     PARSE_ERR(@3, (String("Argument ") + ToString(i+1) + " of built-in function '" + name + "' expects " + acceptedArgTypesStr(fn, i) + " type, but type " + typeStr(args->arg(i)->exprType()) + " was given instead.").c_str());
597 schoenebeck 2581 argsOK = false;
598     break;
599 schoenebeck 2945 } else if (fn->modifiesArg(i) && !args->arg(i)->isModifyable()) {
600     PARSE_ERR(@3, (String("Argument ") + ToString(i+1) + " of built-in function '" + name + "' expects an assignable variable.").c_str());
601     argsOK = false;
602     break;
603 schoenebeck 3582 } else if (isNumber(args->arg(i)->exprType()) && !fn->acceptsArgUnitType(i, args->arg(i)->asNumber()->unitType())) {
604     if (args->arg(i)->asNumber()->unitType())
605     PARSE_ERR(@3, (String("Argument ") + ToString(i+1) + " of built-in function '" + name + "' does not expect unit " + unitTypeStr(args->arg(i)->asNumber()->unitType()) + ".").c_str());
606 schoenebeck 3561 else
607     PARSE_ERR(@3, (String("Argument ") + ToString(i+1) + " of built-in function '" + name + "' expects a unit.").c_str());
608     argsOK = false;
609     break;
610 schoenebeck 3582 } else if (isNumber(args->arg(i)->exprType()) && args->arg(i)->asNumber()->hasUnitFactorEver() && !fn->acceptsArgUnitPrefix(i, args->arg(i)->asNumber()->unitType())) {
611     if (args->arg(i)->asNumber()->unitType())
612     PARSE_ERR(@3, (String("Argument ") + ToString(i+1) + " of built-in function '" + name + "' does not expect a unit prefix for unit" + unitTypeStr(args->arg(i)->asNumber()->unitType()) + ".").c_str());
613 schoenebeck 3564 else
614     PARSE_ERR(@3, (String("Argument ") + ToString(i+1) + " of built-in function '" + name + "' does not expect a unit prefix.").c_str());
615 schoenebeck 3561 argsOK = false;
616     break;
617 schoenebeck 3582 } else if (!fn->acceptsArgFinal(i) && isNumber(args->arg(i)->exprType()) && args->arg(i)->asNumber()->isFinal()) {
618 schoenebeck 3561 PARSE_ERR(@3, (String("Argument ") + ToString(i+1) + " of built-in function '" + name + "' does not expect a \"final\" value.").c_str());
619     argsOK = false;
620     break;
621 schoenebeck 2581 }
622     }
623 schoenebeck 3581 if (argsOK) {
624     // perform built-in function's own, custom arguments checks (if any)
625     fn->checkArgs(&*args, [&](String err) {
626     PARSE_ERR(@3, (String("Built-in function '") + name + "()': " + err).c_str());
627     argsOK = false;
628     }, [&](String wrn) {
629     PARSE_WRN(@3, (String("Built-in function '") + name + "()': " + wrn).c_str());
630     });
631     }
632 schoenebeck 2581 $$ = new FunctionCall(name, args, argsOK ? fn : NULL);
633     }
634     }
635     | IDENTIFIER '(' ')' {
636     const char* name = $1;
637     //printf("function call of '%s' (with empty args)\n", name);
638     ArgsRef args = new Args;
639     VMFunction* fn = context->functionProvider->functionByName(name);
640 schoenebeck 2951 if (context->userFunctionByName(name)) {
641     PARSE_ERR(@1, (String("Missing 'call' keyword before user defined function name '") + name + "'.").c_str());
642     $$ = new FunctionCall(name, args, NULL);
643     } else if (!fn) {
644 schoenebeck 2888 PARSE_ERR(@1, (String("No built-in function with name '") + name + "'.").c_str());
645 schoenebeck 2581 $$ = new FunctionCall(name, args, NULL);
646 schoenebeck 3311 } else if (context->functionProvider->isFunctionDisabled(fn,context)) {
647     PARSE_DROP(@$);
648     $$ = new NoFunctionCall;
649 schoenebeck 2581 } else if (fn->minRequiredArgs() > 0) {
650 schoenebeck 2888 PARSE_ERR(@3, (String("Built-in function '") + name + "' requires at least " + ToString(fn->minRequiredArgs()) + " arguments.").c_str());
651 schoenebeck 2581 $$ = new FunctionCall(name, args, NULL);
652     } else {
653     $$ = new FunctionCall(name, args, fn);
654     }
655     }
656     | IDENTIFIER {
657     const char* name = $1;
658     //printf("function call of '%s' (without args)\n", name);
659     ArgsRef args = new Args;
660     VMFunction* fn = context->functionProvider->functionByName(name);
661 schoenebeck 2951 if (context->userFunctionByName(name)) {
662     PARSE_ERR(@1, (String("Missing 'call' keyword before user defined function name '") + name + "'.").c_str());
663     $$ = new FunctionCall(name, args, NULL);
664     } else if (!fn) {
665 schoenebeck 2888 PARSE_ERR(@1, (String("No built-in function with name '") + name + "'.").c_str());
666 schoenebeck 2581 $$ = new FunctionCall(name, args, NULL);
667 schoenebeck 3311 } else if (context->functionProvider->isFunctionDisabled(fn,context)) {
668     PARSE_DROP(@$);
669     $$ = new NoFunctionCall;
670 schoenebeck 2581 } else if (fn->minRequiredArgs() > 0) {
671 schoenebeck 2888 PARSE_ERR(@1, (String("Built-in function '") + name + "' requires at least " + ToString(fn->minRequiredArgs()) + " arguments.").c_str());
672 schoenebeck 2581 $$ = new FunctionCall(name, args, NULL);
673     } else {
674     $$ = new FunctionCall(name, args, fn);
675     }
676     }
677    
678     args:
679     arg {
680     $$ = new Args();
681     $$->add($1);
682     }
683     | args ',' arg {
684     $$ = $1;
685     $$->add($3);
686     }
687    
688     arg:
689     expr
690    
691 schoenebeck 3728 opt_qualifiers:
692     /* epsilon (empty argument) */ {
693     $$ = QUALIFIER_NONE;
694     }
695     | qualifiers {
696     $$ = $1;
697     }
698    
699     qualifiers:
700     qualifier {
701     $$ = $1;
702     }
703     | qualifiers qualifier {
704     if ($1 & $2)
705     PARSE_ERR(@2, ("Qualifier '" + qualifierStr($2) + "' must only be listed once.").c_str());
706     $$ = (Qualifier_t) ($1 | $2);
707     }
708    
709     qualifier:
710     CONST_ {
711     $$ = QUALIFIER_CONST;
712     }
713     | POLYPHONIC {
714     $$ = QUALIFIER_POLYPHONIC;
715     }
716    
717     opt_assignment:
718     /* epsilon (empty argument) */ {
719     $$ = ExpressionRef();
720     }
721     | ASSIGNMENT expr {
722     $$ = $2;
723     }
724    
725     opt_arr_assignment:
726     /* epsilon (empty argument) */ {
727     $$ = ArgsRef();
728     }
729     | ASSIGNMENT '(' args ')' {
730     $$ = $3;
731     }
732    
733 schoenebeck 2581 assignment:
734     VARIABLE ASSIGNMENT expr {
735     //printf("variable lookup with name '%s' as assignment expr\n", $1);
736     const char* name = $1;
737     VariableRef var = context->variableByName(name);
738     if (!var)
739 schoenebeck 2888 PARSE_ERR(@1, (String("Variable assignment: No variable declared with name '") + name + "'.").c_str());
740 schoenebeck 2581 else if (var->isConstExpr())
741 schoenebeck 2888 PARSE_ERR(@2, (String("Variable assignment: Cannot modify const variable '") + name + "'.").c_str());
742 schoenebeck 2942 else if (!var->isAssignable())
743     PARSE_ERR(@2, (String("Variable assignment: Variable '") + name + "' is not assignable.").c_str());
744 schoenebeck 2581 else if (var->exprType() != $3->exprType())
745 schoenebeck 2888 PARSE_ERR(@3, (String("Variable assignment: Variable '") + name + "' is of type " + typeStr(var->exprType()) + ", assignment is of type " + typeStr($3->exprType()) + " though.").c_str());
746 schoenebeck 3582 else if (isNumber(var->exprType())) {
747     NumberVariableRef numberVar = var;
748     NumberExprRef expr = $3;
749 schoenebeck 3573 if (numberVar->unitType() != expr->unitType())
750     PARSE_ERR(@3, (String("Variable assignment: Variable '") + name + "' has unit type " + unitTypeStr(numberVar->unitType()) + ", assignment has unit type " + unitTypeStr(expr->unitType()) + " though.").c_str());
751     else if (numberVar->isFinal() != expr->isFinal())
752     PARSE_ERR(@3, (String("Variable assignment: Variable '") + name + "' was declared as " + String(numberVar->isFinal() ? "final" : "not final") + ", assignment is " + String(expr->isFinal() ? "final" : "not final") + " though.").c_str());
753 schoenebeck 3561 }
754 schoenebeck 2581 $$ = new Assignment(var, $3);
755     }
756     | VARIABLE '[' expr ']' ASSIGNMENT expr {
757     const char* name = $1;
758     VariableRef var = context->variableByName(name);
759     if (!var)
760 schoenebeck 2888 PARSE_ERR(@1, (String("No variable declared with name '") + name + "'.").c_str());
761 schoenebeck 3573 else if (!isArray(var->exprType()))
762 schoenebeck 2888 PARSE_ERR(@2, (String("Variable '") + name + "' is not an array variable.").c_str());
763 schoenebeck 3253 else if (var->isConstExpr())
764     PARSE_ERR(@5, (String("Variable assignment: Cannot modify const array variable '") + name + "'.").c_str());
765     else if (!var->isAssignable())
766     PARSE_ERR(@5, (String("Variable assignment: Array variable '") + name + "' is not assignable.").c_str());
767 schoenebeck 2581 else if ($3->exprType() != INT_EXPR)
768 schoenebeck 2888 PARSE_ERR(@3, (String("Array variable '") + name + "' accessed with non integer expression.").c_str());
769 schoenebeck 3561 else if ($3->asInt()->unitType())
770     PARSE_ERR(@3, "Unit types are not allowed as array index.");
771 schoenebeck 3586 else if ($6->exprType() != scalarTypeOfArray(var->exprType()))
772 schoenebeck 3573 PARSE_ERR(@5, (String("Variable '") + name + "' was declared as " + typeStr(var->exprType()) + ", assigned expression is " + typeStr($6->exprType()) + " though.").c_str());
773 schoenebeck 3582 else if ($6->asNumber()->unitType())
774 schoenebeck 3561 PARSE_ERR(@6, "Unit types are not allowed for array variables.");
775 schoenebeck 3582 else if ($6->asNumber()->isFinal())
776 schoenebeck 3561 PARSE_ERR(@6, "Final operator '!' not allowed for array variables.");
777 schoenebeck 3573 else if ($3->isConstExpr() && $3->asInt()->evalInt() >= ((ArrayExprRef)var)->arraySize())
778 schoenebeck 3257 PARSE_WRN(@3, (String("Index ") + ToString($3->asInt()->evalInt()) +
779     " exceeds size of array variable '" + name +
780     "' which was declared with size " +
781 schoenebeck 3573 ToString(((ArrayExprRef)var)->arraySize()) + ".").c_str());
782 schoenebeck 3561 else if ($3->asInt()->isFinal())
783     PARSE_WRN(@3, "Final operator '!' is meaningless here.");
784 schoenebeck 3573 if (var->exprType() == INT_ARR_EXPR) {
785     IntArrayElementRef element = new IntArrayElement(var, $3);
786     $$ = new Assignment(element, $6);
787     } else if (var->exprType() == REAL_ARR_EXPR) {
788     RealArrayElementRef element = new RealArrayElement(var, $3);
789     $$ = new Assignment(element, $6);
790     } else {
791 schoenebeck 3581 $$ = new NoOperation; // actually not possible to ever get here
792 schoenebeck 3573 }
793 schoenebeck 2581 }
794    
795     unary_expr:
796     INTEGER {
797 schoenebeck 3581 $$ = new IntLiteral({ .value = $1 });
798 schoenebeck 2581 }
799 schoenebeck 3573 | REAL {
800 schoenebeck 3581 $$ = new RealLiteral({ .value = $1 });
801 schoenebeck 3573 }
802 schoenebeck 3561 | INTEGER_UNIT {
803 schoenebeck 3581 IntLiteralRef literal = new IntLiteral({
804     .value = $1.iValue,
805     .unitFactor = VMUnit::unitFactor($1.prefix),
806     .unitType = $1.unit
807     });
808 schoenebeck 3561 $$ = literal;
809     }
810 schoenebeck 3573 | REAL_UNIT {
811 schoenebeck 3581 RealLiteralRef literal = new RealLiteral({
812     .value = $1.fValue,
813     .unitFactor = VMUnit::unitFactor($1.prefix),
814     .unitType = $1.unit
815     });
816 schoenebeck 3573 $$ = literal;
817     }
818 schoenebeck 2581 | STRING {
819     $$ = new StringLiteral($1);
820     }
821     | VARIABLE {
822     //printf("variable lookup with name '%s' as unary expr\n", $1);
823     VariableRef var = context->variableByName($1);
824     if (var)
825     $$ = var;
826     else {
827 schoenebeck 2888 PARSE_ERR(@1, (String("No variable declared with name '") + $1 + "'.").c_str());
828 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
829 schoenebeck 2581 }
830     }
831     | VARIABLE '[' expr ']' {
832     const char* name = $1;
833     VariableRef var = context->variableByName(name);
834     if (!var) {
835 schoenebeck 2888 PARSE_ERR(@1, (String("No variable declared with name '") + name + "'.").c_str());
836 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
837 schoenebeck 3573 } else if (!isArray(var->exprType())) {
838 schoenebeck 2888 PARSE_ERR(@2, (String("Variable '") + name + "' is not an array variable.").c_str());
839 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
840 schoenebeck 2581 } else if ($3->exprType() != INT_EXPR) {
841 schoenebeck 2888 PARSE_ERR(@3, (String("Array variable '") + name + "' accessed with non integer expression.").c_str());
842 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
843     } else if ($3->asInt()->unitType() || $3->asInt()->hasUnitFactorEver()) {
844 schoenebeck 3561 PARSE_ERR(@3, "Units are not allowed as array index.");
845 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
846 schoenebeck 2581 } else {
847 schoenebeck 3573 if ($3->isConstExpr() && $3->asInt()->evalInt() >= ((ArrayExprRef)var)->arraySize())
848 schoenebeck 3257 PARSE_WRN(@3, (String("Index ") + ToString($3->asInt()->evalInt()) +
849     " exceeds size of array variable '" + name +
850     "' which was declared with size " +
851 schoenebeck 3573 ToString(((ArrayExprRef)var)->arraySize()) + ".").c_str());
852 schoenebeck 3561 else if ($3->asInt()->isFinal())
853     PARSE_WRN(@3, "Final operator '!' is meaningless here.");
854 schoenebeck 3573 if (var->exprType() == REAL_ARR_EXPR) {
855     $$ = new RealArrayElement(var, $3);
856     } else {
857     $$ = new IntArrayElement(var, $3);
858     }
859 schoenebeck 2581 }
860     }
861     | '(' expr ')' {
862     $$ = $2;
863     }
864     | functioncall {
865     $$ = $1;
866     }
867 schoenebeck 3592 | '+' unary_expr {
868     $$ = $2;
869     }
870 schoenebeck 2581 | '-' unary_expr {
871     $$ = new Neg($2);
872     }
873 schoenebeck 2935 | BITWISE_NOT unary_expr {
874     if ($2->exprType() != INT_EXPR) {
875     PARSE_ERR(@2, (String("Right operand of bitwise operator '.not.' must be an integer expression, is ") + typeStr($2->exprType()) + " though.").c_str());
876 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
877     } else if ($2->asInt()->unitType() || $2->asInt()->hasUnitFactorEver()) {
878 schoenebeck 3561 PARSE_ERR(@2, "Units are not allowed for operands of bitwise operations.");
879 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
880 schoenebeck 2935 } else {
881     $$ = new BitwiseNot($2);
882     }
883     }
884 schoenebeck 2581 | NOT unary_expr {
885     if ($2->exprType() != INT_EXPR) {
886 schoenebeck 2888 PARSE_ERR(@2, (String("Right operand of operator 'not' must be an integer expression, is ") + typeStr($2->exprType()) + " though.").c_str());
887 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
888     } else if ($2->asInt()->unitType() || $2->asInt()->hasUnitFactorEver()) {
889 schoenebeck 3561 PARSE_ERR(@2, "Units are not allowed for operands of logical operations.");
890 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
891 schoenebeck 2581 } else {
892     $$ = new Not($2);
893     }
894     }
895 schoenebeck 3561 | '!' unary_expr {
896 schoenebeck 3582 if (!isNumber($2->exprType())) {
897 schoenebeck 3573 PARSE_ERR(@2, (String("Right operand of \"final\" operator '!' must be a scalar number expression, is ") + typeStr($2->exprType()) + " though.").c_str());
898 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
899 schoenebeck 3561 } else {
900     $$ = new Final($2);
901     }
902     }
903 schoenebeck 2581
904     expr:
905     concat_expr
906    
907     concat_expr:
908 schoenebeck 2935 logical_or_expr
909     | concat_expr '&' logical_or_expr {
910 schoenebeck 2581 ExpressionRef lhs = $1;
911     ExpressionRef rhs = $3;
912     if (lhs->isConstExpr() && rhs->isConstExpr()) {
913     $$ = new StringLiteral(
914     lhs->evalCastToStr() + rhs->evalCastToStr()
915     );
916     } else {
917     $$ = new ConcatString(lhs, rhs);
918     }
919     }
920    
921 schoenebeck 2935 logical_or_expr:
922     logical_and_expr
923     | logical_or_expr OR logical_and_expr {
924 schoenebeck 2581 ExpressionRef lhs = $1;
925     ExpressionRef rhs = $3;
926     if (lhs->exprType() != INT_EXPR) {
927 schoenebeck 2888 PARSE_ERR(@1, (String("Left operand of operator 'or' must be an integer expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
928 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
929 schoenebeck 2581 } else if (rhs->exprType() != INT_EXPR) {
930 schoenebeck 2888 PARSE_ERR(@3, (String("Right operand of operator 'or' must be an integer expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
931 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
932     } else if (lhs->asInt()->unitType() || lhs->asInt()->hasUnitFactorEver()) {
933 schoenebeck 3561 PARSE_ERR(@1, "Units are not allowed for operands of logical operations.");
934 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
935     } else if (rhs->asInt()->unitType() || rhs->asInt()->hasUnitFactorEver()) {
936 schoenebeck 3561 PARSE_ERR(@3, "Units are not allowed for operands of logical operations.");
937 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
938 schoenebeck 2581 } else {
939 schoenebeck 3581 if (lhs->asInt()->isFinal() && !rhs->asInt()->isFinal())
940     PARSE_WRN(@3, "Right operand of 'or' operation is not 'final', result will be 'final' though since left operand is 'final'.");
941     else if (!lhs->asInt()->isFinal() && rhs->asInt()->isFinal())
942     PARSE_WRN(@1, "Left operand of 'or' operation is not 'final', result will be 'final' though since right operand is 'final'.");
943 schoenebeck 2581 $$ = new Or(lhs, rhs);
944     }
945     }
946    
947 schoenebeck 2935 logical_and_expr:
948     bitwise_or_expr {
949 schoenebeck 2581 $$ = $1;
950     }
951 schoenebeck 2935 | logical_and_expr AND bitwise_or_expr {
952 schoenebeck 2581 ExpressionRef lhs = $1;
953     ExpressionRef rhs = $3;
954     if (lhs->exprType() != INT_EXPR) {
955 schoenebeck 2888 PARSE_ERR(@1, (String("Left operand of operator 'and' must be an integer expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
956 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
957 schoenebeck 2581 } else if (rhs->exprType() != INT_EXPR) {
958 schoenebeck 2888 PARSE_ERR(@3, (String("Right operand of operator 'and' must be an integer expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
959 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
960     } else if (lhs->asInt()->unitType() || lhs->asInt()->hasUnitFactorEver()) {
961 schoenebeck 3561 PARSE_ERR(@1, "Units are not allowed for operands of logical operations.");
962 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
963     } else if (rhs->asInt()->unitType() || rhs->asInt()->hasUnitFactorEver()) {
964 schoenebeck 3561 PARSE_ERR(@3, "Units are not allowed for operands of logical operations.");
965 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
966 schoenebeck 2581 } else {
967 schoenebeck 3581 if (lhs->asInt()->isFinal() && !rhs->asInt()->isFinal())
968     PARSE_WRN(@3, "Right operand of 'and' operation is not 'final', result will be 'final' though since left operand is 'final'.");
969     else if (!lhs->asInt()->isFinal() && rhs->asInt()->isFinal())
970     PARSE_WRN(@1, "Left operand of 'and' operation is not 'final', result will be 'final' though since right operand is 'final'.");
971 schoenebeck 2581 $$ = new And(lhs, rhs);
972     }
973     }
974    
975 schoenebeck 2935 bitwise_or_expr:
976     bitwise_and_expr
977     | bitwise_or_expr BITWISE_OR bitwise_and_expr {
978     ExpressionRef lhs = $1;
979     ExpressionRef rhs = $3;
980     if (lhs->exprType() != INT_EXPR) {
981     PARSE_ERR(@1, (String("Left operand of bitwise operator '.or.' must be an integer expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
982 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
983 schoenebeck 2935 } else if (rhs->exprType() != INT_EXPR) {
984     PARSE_ERR(@3, (String("Right operand of bitwise operator '.or.' must be an integer expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
985 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
986     } else if (lhs->asInt()->unitType() || lhs->asInt()->hasUnitFactorEver()) {
987 schoenebeck 3561 PARSE_ERR(@1, "Units are not allowed for operands of bitwise operations.");
988 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
989     } else if (rhs->asInt()->unitType() || rhs->asInt()->hasUnitFactorEver()) {
990 schoenebeck 3561 PARSE_ERR(@3, "Units are not allowed for operands of bitwise operations.");
991 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
992 schoenebeck 2935 } else {
993 schoenebeck 3581 if (lhs->asInt()->isFinal() && !rhs->asInt()->isFinal())
994     PARSE_WRN(@3, "Right operand of '.or.' operation is not 'final', result will be 'final' though since left operand is 'final'.");
995     else if (!lhs->asInt()->isFinal() && rhs->asInt()->isFinal())
996     PARSE_WRN(@1, "Left operand of '.or.' operation is not 'final', result will be 'final' though since right operand is 'final'.");
997 schoenebeck 2935 $$ = new BitwiseOr(lhs, rhs);
998     }
999     }
1000    
1001     bitwise_and_expr:
1002     rel_expr {
1003     $$ = $1;
1004     }
1005     | bitwise_and_expr BITWISE_AND rel_expr {
1006     ExpressionRef lhs = $1;
1007     ExpressionRef rhs = $3;
1008     if (lhs->exprType() != INT_EXPR) {
1009     PARSE_ERR(@1, (String("Left operand of bitwise operator '.and.' must be an integer expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
1010 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1011 schoenebeck 2935 } else if (rhs->exprType() != INT_EXPR) {
1012     PARSE_ERR(@3, (String("Right operand of bitwise operator '.and.' must be an integer expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
1013 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1014     } else if (lhs->asInt()->unitType() || lhs->asInt()->hasUnitFactorEver()) {
1015 schoenebeck 3561 PARSE_ERR(@1, "Units are not allowed for operands of bitwise operations.");
1016 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1017     } else if (rhs->asInt()->unitType() || rhs->asInt()->hasUnitFactorEver()) {
1018 schoenebeck 3561 PARSE_ERR(@3, "Units are not allowed for operands of bitwise operations.");
1019 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1020 schoenebeck 2935 } else {
1021 schoenebeck 3581 if (lhs->asInt()->isFinal() && !rhs->asInt()->isFinal())
1022     PARSE_WRN(@3, "Right operand of '.and.' operation is not 'final', result will be 'final' though since left operand is 'final'.");
1023     else if (!lhs->asInt()->isFinal() && rhs->asInt()->isFinal())
1024     PARSE_WRN(@1, "Left operand of '.and.' operation is not 'final', result will be 'final' though since right operand is 'final'.");
1025 schoenebeck 2935 $$ = new BitwiseAnd(lhs, rhs);
1026     }
1027     }
1028    
1029 schoenebeck 2581 rel_expr:
1030     add_expr
1031     | rel_expr '<' add_expr {
1032     ExpressionRef lhs = $1;
1033     ExpressionRef rhs = $3;
1034 schoenebeck 3582 if (!isNumber(lhs->exprType())) {
1035 schoenebeck 3573 PARSE_ERR(@1, (String("Left operand of operator '<' must be a scalar number expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
1036 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1037 schoenebeck 3582 } else if (!isNumber(rhs->exprType())) {
1038 schoenebeck 3573 PARSE_ERR(@3, (String("Right operand of operator '<' must be a scalar number expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
1039 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1040 schoenebeck 3582 } else if (lhs->asNumber()->unitType() != rhs->asNumber()->unitType()) {
1041 schoenebeck 3581 PARSE_ERR(@2, (String("Operands of relative operations must have same unit, left operand is ") +
1042 schoenebeck 3582 unitTypeStr(lhs->asNumber()->unitType()) + " and right operand is " +
1043     unitTypeStr(rhs->asNumber()->unitType()) + " though.").c_str());
1044 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1045 schoenebeck 2581 } else {
1046 schoenebeck 3582 if (lhs->asNumber()->isFinal() && !rhs->asNumber()->isFinal())
1047 schoenebeck 3581 PARSE_WRN(@3, "Right operand of '<' comparison is not 'final', left operand is 'final' though.");
1048 schoenebeck 3582 else if (!lhs->asNumber()->isFinal() && rhs->asNumber()->isFinal())
1049 schoenebeck 3581 PARSE_WRN(@1, "Left operand of '<' comparison is not 'final', right operand is 'final' though.");
1050 schoenebeck 2581 $$ = new Relation(lhs, Relation::LESS_THAN, rhs);
1051     }
1052     }
1053     | rel_expr '>' add_expr {
1054     ExpressionRef lhs = $1;
1055     ExpressionRef rhs = $3;
1056 schoenebeck 3582 if (!isNumber(lhs->exprType())) {
1057 schoenebeck 3573 PARSE_ERR(@1, (String("Left operand of operator '>' must be a scalar number expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
1058 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1059 schoenebeck 3582 } else if (!isNumber(rhs->exprType())) {
1060 schoenebeck 3573 PARSE_ERR(@3, (String("Right operand of operator '>' must be a scalar number expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
1061 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1062 schoenebeck 3582 } else if (lhs->asNumber()->unitType() != rhs->asNumber()->unitType()) {
1063 schoenebeck 3581 PARSE_ERR(@2, (String("Operands of relative operations must have same unit, left operand is ") +
1064 schoenebeck 3582 unitTypeStr(lhs->asNumber()->unitType()) + " and right operand is " +
1065     unitTypeStr(rhs->asNumber()->unitType()) + " though.").c_str());
1066 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1067 schoenebeck 2581 } else {
1068 schoenebeck 3582 if (lhs->asNumber()->isFinal() && !rhs->asNumber()->isFinal())
1069 schoenebeck 3581 PARSE_WRN(@3, "Right operand of '>' comparison is not 'final', left operand is 'final' though.");
1070 schoenebeck 3582 else if (!lhs->asNumber()->isFinal() && rhs->asNumber()->isFinal())
1071 schoenebeck 3581 PARSE_WRN(@1, "Left operand of '>' comparison is not 'final', right operand is 'final' though.");
1072 schoenebeck 2581 $$ = new Relation(lhs, Relation::GREATER_THAN, rhs);
1073     }
1074     }
1075     | rel_expr LE add_expr {
1076     ExpressionRef lhs = $1;
1077     ExpressionRef rhs = $3;
1078 schoenebeck 3582 if (!isNumber(lhs->exprType())) {
1079 schoenebeck 3573 PARSE_ERR(@1, (String("Left operand of operator '<=' must be a scalar number expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
1080 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1081 schoenebeck 3582 } else if (!isNumber(rhs->exprType())) {
1082 schoenebeck 3573 PARSE_ERR(@3, (String("Right operand of operator '<=' must be a scalar number expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
1083 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1084 schoenebeck 3582 } else if (lhs->asNumber()->unitType() != rhs->asNumber()->unitType()) {
1085 schoenebeck 3581 PARSE_ERR(@2, (String("Operands of relative operations must have same unit, left operand is ") +
1086 schoenebeck 3582 unitTypeStr(lhs->asNumber()->unitType()) + " and right operand is " +
1087     unitTypeStr(rhs->asNumber()->unitType()) + " though.").c_str());
1088 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1089 schoenebeck 2581 } else {
1090 schoenebeck 3582 if (lhs->asNumber()->isFinal() && !rhs->asNumber()->isFinal())
1091 schoenebeck 3581 PARSE_WRN(@3, "Right operand of '<=' comparison is not 'final', left operand is 'final' though.");
1092 schoenebeck 3582 else if (!lhs->asNumber()->isFinal() && rhs->asNumber()->isFinal())
1093 schoenebeck 3581 PARSE_WRN(@1, "Left operand of '<=' comparison is not 'final', right operand is 'final' though.");
1094 schoenebeck 2581 $$ = new Relation(lhs, Relation::LESS_OR_EQUAL, rhs);
1095     }
1096     }
1097     | rel_expr GE add_expr {
1098     ExpressionRef lhs = $1;
1099     ExpressionRef rhs = $3;
1100 schoenebeck 3582 if (!isNumber(lhs->exprType())) {
1101 schoenebeck 3573 PARSE_ERR(@1, (String("Left operand of operator '>=' must be a scalar number expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
1102 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1103 schoenebeck 3582 } else if (!isNumber(rhs->exprType())) {
1104 schoenebeck 3573 PARSE_ERR(@3, (String("Right operand of operator '>=' must be a scalar number expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
1105 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1106 schoenebeck 3582 } else if (lhs->asNumber()->unitType() != rhs->asNumber()->unitType()) {
1107 schoenebeck 3581 PARSE_ERR(@2, (String("Operands of relative operations must have same unit, left operand is ") +
1108 schoenebeck 3582 unitTypeStr(lhs->asNumber()->unitType()) + " and right operand is " +
1109     unitTypeStr(rhs->asNumber()->unitType()) + " though.").c_str());
1110 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1111 schoenebeck 2581 } else {
1112 schoenebeck 3582 if (lhs->asNumber()->isFinal() && !rhs->asNumber()->isFinal())
1113 schoenebeck 3581 PARSE_WRN(@3, "Right operand of '>=' comparison is not 'final', left operand is 'final' though.");
1114 schoenebeck 3582 else if (!lhs->asNumber()->isFinal() && rhs->asNumber()->isFinal())
1115 schoenebeck 3581 PARSE_WRN(@1, "Left operand of '>=' comparison is not 'final', right operand is 'final' though.");
1116 schoenebeck 2581 $$ = new Relation(lhs, Relation::GREATER_OR_EQUAL, rhs);
1117     }
1118     }
1119     | rel_expr '=' add_expr {
1120 schoenebeck 3561 ExpressionRef lhs = $1;
1121     ExpressionRef rhs = $3;
1122 schoenebeck 3582 if (!isNumber(lhs->exprType())) {
1123 schoenebeck 3573 PARSE_ERR(@1, (String("Left operand of operator '=' must be a scalar number expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
1124 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1125 schoenebeck 3582 } else if (!isNumber(rhs->exprType())) {
1126 schoenebeck 3573 PARSE_ERR(@3, (String("Right operand of operator '=' must be a scalar number expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
1127 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1128 schoenebeck 3582 } else if (lhs->asNumber()->unitType() != rhs->asNumber()->unitType()) {
1129 schoenebeck 3581 PARSE_ERR(@2, (String("Operands of relative operations must have same unit, left operand is ") +
1130 schoenebeck 3582 unitTypeStr(lhs->asNumber()->unitType()) + " and right operand is " +
1131     unitTypeStr(rhs->asNumber()->unitType()) + " though.").c_str());
1132 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1133 schoenebeck 3561 } else {
1134 schoenebeck 3582 if (lhs->asNumber()->isFinal() && !rhs->asNumber()->isFinal())
1135 schoenebeck 3581 PARSE_WRN(@3, "Right operand of '=' comparison is not 'final', left operand is 'final' though.");
1136 schoenebeck 3582 else if (!lhs->asNumber()->isFinal() && rhs->asNumber()->isFinal())
1137 schoenebeck 3581 PARSE_WRN(@1, "Left operand of '=' comparison is not 'final', right operand is 'final' though.");
1138 schoenebeck 3561 $$ = new Relation(lhs, Relation::EQUAL, rhs);
1139     }
1140 schoenebeck 2581 }
1141     | rel_expr '#' add_expr {
1142 schoenebeck 3561 ExpressionRef lhs = $1;
1143     ExpressionRef rhs = $3;
1144 schoenebeck 3582 if (!isNumber(lhs->exprType())) {
1145 schoenebeck 3573 PARSE_ERR(@1, (String("Left operand of operator '#' must be a scalar number expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
1146 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1147 schoenebeck 3582 } else if (!isNumber(rhs->exprType())) {
1148 schoenebeck 3573 PARSE_ERR(@3, (String("Right operand of operator '#' must be a scalar number expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
1149 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1150 schoenebeck 3582 } else if (lhs->asNumber()->unitType() != rhs->asNumber()->unitType()) {
1151 schoenebeck 3581 PARSE_ERR(@2, (String("Operands of relative operations must have same unit, left operand is ") +
1152 schoenebeck 3582 unitTypeStr(lhs->asNumber()->unitType()) + " and right operand is " +
1153     unitTypeStr(rhs->asNumber()->unitType()) + " though.").c_str());
1154 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1155 schoenebeck 3561 } else {
1156 schoenebeck 3582 if (lhs->asNumber()->isFinal() && !rhs->asNumber()->isFinal())
1157 schoenebeck 3581 PARSE_WRN(@3, "Right operand of '#' comparison is not 'final', left operand is 'final' though.");
1158 schoenebeck 3582 else if (!lhs->asNumber()->isFinal() && rhs->asNumber()->isFinal())
1159 schoenebeck 3581 PARSE_WRN(@1, "Left operand of '#' comparison is not 'final', right operand is 'final' though.");
1160 schoenebeck 3561 $$ = new Relation(lhs, Relation::NOT_EQUAL, rhs);
1161     }
1162 schoenebeck 2581 }
1163    
1164     add_expr:
1165     mul_expr
1166     | add_expr '+' mul_expr {
1167     ExpressionRef lhs = $1;
1168     ExpressionRef rhs = $3;
1169 schoenebeck 3582 if (!isNumber(lhs->exprType())) {
1170 schoenebeck 3573 PARSE_ERR(@1, (String("Left operand of operator '+' must be a scalar number expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
1171 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1172 schoenebeck 3582 } else if (!isNumber(rhs->exprType())) {
1173 schoenebeck 3573 PARSE_ERR(@1, (String("Right operand of operator '+' must be a scalar number expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
1174 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1175 schoenebeck 3573 } else if (lhs->exprType() != rhs->exprType()) {
1176     PARSE_ERR(@2, (String("Operands of operator '+' must have same type; left operand is ") +
1177     typeStr(lhs->exprType()) + " and right operand is " + typeStr(rhs->exprType()) + " though.").c_str());
1178 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1179 schoenebeck 3582 } else if (lhs->asNumber()->unitType() != rhs->asNumber()->unitType()) {
1180 schoenebeck 3581 PARSE_ERR(@2, (String("Operands of '+' operations must have same unit, left operand is ") +
1181 schoenebeck 3582 unitTypeStr(lhs->asNumber()->unitType()) + " and right operand is " +
1182     unitTypeStr(rhs->asNumber()->unitType()) + " though.").c_str());
1183 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1184 schoenebeck 2581 } else {
1185 schoenebeck 3582 if (lhs->asNumber()->isFinal() && !rhs->asNumber()->isFinal())
1186 schoenebeck 3581 PARSE_WRN(@3, "Right operand of '+' operation is not 'final', result will be 'final' though since left operand is 'final'.");
1187 schoenebeck 3582 else if (!lhs->asNumber()->isFinal() && rhs->asNumber()->isFinal())
1188 schoenebeck 3581 PARSE_WRN(@1, "Left operand of '+' operation is not 'final', result will be 'final' though since right operand is 'final'.");
1189 schoenebeck 2581 $$ = new Add(lhs,rhs);
1190     }
1191     }
1192     | add_expr '-' mul_expr {
1193     ExpressionRef lhs = $1;
1194     ExpressionRef rhs = $3;
1195 schoenebeck 3582 if (!isNumber(lhs->exprType())) {
1196 schoenebeck 3573 PARSE_ERR(@1, (String("Left operand of operator '-' must be a scalar number expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
1197 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1198 schoenebeck 3582 } else if (!isNumber(rhs->exprType())) {
1199 schoenebeck 3573 PARSE_ERR(@1, (String("Right operand of operator '-' must be a scalar number expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
1200 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1201 schoenebeck 3573 } else if (lhs->exprType() != rhs->exprType()) {
1202     PARSE_ERR(@2, (String("Operands of operator '-' must have same type; left operand is ") +
1203     typeStr(lhs->exprType()) + " and right operand is " + typeStr(rhs->exprType()) + " though.").c_str());
1204 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1205 schoenebeck 3582 } else if (lhs->asNumber()->unitType() != rhs->asNumber()->unitType()) {
1206 schoenebeck 3581 PARSE_ERR(@2, (String("Operands of '-' operations must have same unit, left operand is ") +
1207 schoenebeck 3582 unitTypeStr(lhs->asNumber()->unitType()) + " and right operand is " +
1208     unitTypeStr(rhs->asNumber()->unitType()) + " though.").c_str());
1209 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1210 schoenebeck 2581 } else {
1211 schoenebeck 3582 if (lhs->asNumber()->isFinal() && !rhs->asNumber()->isFinal())
1212 schoenebeck 3581 PARSE_WRN(@3, "Right operand of '-' operation is not 'final', result will be 'final' though since left operand is 'final'.");
1213 schoenebeck 3582 else if (!lhs->asNumber()->isFinal() && rhs->asNumber()->isFinal())
1214 schoenebeck 3581 PARSE_WRN(@1, "Left operand of '-' operation is not 'final', result will be 'final' though since right operand is 'final'.");
1215 schoenebeck 2581 $$ = new Sub(lhs,rhs);
1216     }
1217     }
1218    
1219     mul_expr:
1220     unary_expr
1221     | mul_expr '*' unary_expr {
1222     ExpressionRef lhs = $1;
1223     ExpressionRef rhs = $3;
1224 schoenebeck 3582 if (!isNumber(lhs->exprType())) {
1225 schoenebeck 3573 PARSE_ERR(@1, (String("Left operand of operator '*' must be a scalar number expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
1226 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1227 schoenebeck 3582 } else if (!isNumber(rhs->exprType())) {
1228 schoenebeck 3573 PARSE_ERR(@1, (String("Right operand of operator '*' must be a scalar number expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
1229 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1230 schoenebeck 3582 } else if (lhs->asNumber()->unitType() && rhs->asNumber()->unitType()) {
1231 schoenebeck 3581 PARSE_ERR(@2, (String("Only one operand of operator '*' may have a unit type, left operand is ") +
1232 schoenebeck 3582 unitTypeStr(lhs->asNumber()->unitType()) + " and right operand is " +
1233     unitTypeStr(rhs->asNumber()->unitType()) + " though.").c_str());
1234 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1235 schoenebeck 3573 } else if (lhs->exprType() != rhs->exprType()) {
1236     PARSE_ERR(@2, (String("Operands of operator '*' must have same type; left operand is ") +
1237     typeStr(lhs->exprType()) + " and right operand is " + typeStr(rhs->exprType()) + " though.").c_str());
1238 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1239 schoenebeck 2581 } else {
1240 schoenebeck 3582 if (lhs->asNumber()->isFinal() && !rhs->asNumber()->isFinal())
1241 schoenebeck 3581 PARSE_WRN(@3, "Right operand of '*' operation is not 'final', result will be 'final' though since left operand is 'final'.");
1242 schoenebeck 3582 else if (!lhs->asNumber()->isFinal() && rhs->asNumber()->isFinal())
1243 schoenebeck 3581 PARSE_WRN(@1, "Left operand of '*' operation is not 'final', result will be 'final' though since right operand is 'final'.");
1244 schoenebeck 2581 $$ = new Mul(lhs,rhs);
1245     }
1246     }
1247     | mul_expr '/' unary_expr {
1248     ExpressionRef lhs = $1;
1249     ExpressionRef rhs = $3;
1250 schoenebeck 3582 if (!isNumber(lhs->exprType())) {
1251 schoenebeck 3573 PARSE_ERR(@1, (String("Left operand of operator '/' must be a scalar number expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
1252 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1253 schoenebeck 3582 } else if (!isNumber(rhs->exprType())) {
1254 schoenebeck 3573 PARSE_ERR(@1, (String("Right operand of operator '/' must be a scalar number expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
1255 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1256 schoenebeck 3582 } else if (lhs->asNumber()->unitType() && rhs->asNumber()->unitType() &&
1257     lhs->asNumber()->unitType() != rhs->asNumber()->unitType())
1258 schoenebeck 3561 {
1259 schoenebeck 3581 PARSE_ERR(@2, (String("Operands of operator '/' with two different unit types, left operand is ") +
1260 schoenebeck 3582 unitTypeStr(lhs->asNumber()->unitType()) + " and right operand is " +
1261     unitTypeStr(rhs->asNumber()->unitType()) + " though.").c_str());
1262 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1263 schoenebeck 3582 } else if (!lhs->asNumber()->unitType() && rhs->asNumber()->unitType()) {
1264 schoenebeck 3581 PARSE_ERR(@3, ("Dividing left operand without any unit type by right operand with unit type (" +
1265 schoenebeck 3582 unitTypeStr(rhs->asNumber()->unitType()) + ") is not possible.").c_str());
1266 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1267 schoenebeck 3573 } else if (lhs->exprType() != rhs->exprType()) {
1268     PARSE_ERR(@2, (String("Operands of operator '/' must have same type; left operand is ") +
1269     typeStr(lhs->exprType()) + " and right operand is " + typeStr(rhs->exprType()) + " though.").c_str());
1270 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1271 schoenebeck 2581 } else {
1272 schoenebeck 3582 if (lhs->asNumber()->isFinal() && !rhs->asNumber()->isFinal())
1273 schoenebeck 3581 PARSE_WRN(@3, "Right operand of '/' operation is not 'final', result will be 'final' though since left operand is 'final'.");
1274 schoenebeck 3582 else if (!lhs->asNumber()->isFinal() && rhs->asNumber()->isFinal())
1275 schoenebeck 3581 PARSE_WRN(@1, "Left operand of '/' operation is not 'final', result will be 'final' though since right operand is 'final'.");
1276 schoenebeck 2581 $$ = new Div(lhs,rhs);
1277     }
1278     }
1279     | mul_expr MOD unary_expr {
1280     ExpressionRef lhs = $1;
1281     ExpressionRef rhs = $3;
1282     if (lhs->exprType() != INT_EXPR) {
1283 schoenebeck 2888 PARSE_ERR(@1, (String("Left operand of modulo operator must be an integer expression, is ") + typeStr(lhs->exprType()) + " though.").c_str());
1284 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1285 schoenebeck 2581 } else if (rhs->exprType() != INT_EXPR) {
1286 schoenebeck 2888 PARSE_ERR(@3, (String("Right operand of modulo operator must be an integer expression, is ") + typeStr(rhs->exprType()) + " though.").c_str());
1287 schoenebeck 3581 $$ = new IntLiteral({ .value = 0 });
1288 schoenebeck 2581 } else {
1289 schoenebeck 3581 if (lhs->asInt()->unitType() || lhs->asInt()->hasUnitFactorEver())
1290 schoenebeck 3561 PARSE_ERR(@1, "Operands of modulo operator must not use any unit.");
1291 schoenebeck 3581 if (rhs->asInt()->unitType() || rhs->asInt()->hasUnitFactorEver())
1292 schoenebeck 3561 PARSE_ERR(@3, "Operands of modulo operator must not use any unit.");
1293 schoenebeck 3581 if (lhs->asInt()->isFinal() && !rhs->asInt()->isFinal())
1294     PARSE_WRN(@3, "Right operand of 'mod' operation is not 'final', result will be 'final' though since left operand is 'final'.");
1295     else if (!lhs->asInt()->isFinal() && rhs->asInt()->isFinal())
1296     PARSE_WRN(@1, "Left operand of 'mod' operation is not 'final', result will be 'final' though since right operand is 'final'.");
1297 schoenebeck 2581 $$ = new Mod(lhs,rhs);
1298     }
1299     }
1300    
1301     %%
1302    
1303     void InstrScript_error(YYLTYPE* locp, LinuxSampler::ParserContext* context, const char* err) {
1304     //fprintf(stderr, "%d: %s\n", locp->first_line, err);
1305 schoenebeck 2889 context->addErr(locp->first_line, locp->last_line, locp->first_column+1, locp->last_column+1, err);
1306 schoenebeck 2581 }
1307    
1308     void InstrScript_warning(YYLTYPE* locp, LinuxSampler::ParserContext* context, const char* txt) {
1309     //fprintf(stderr, "WRN %d: %s\n", locp->first_line, txt);
1310 schoenebeck 2889 context->addWrn(locp->first_line, locp->last_line, locp->first_column+1, locp->last_column+1, txt);
1311 schoenebeck 2581 }
1312 schoenebeck 3008
1313     /// Custom implementation of yytnamerr() to ensure quotation is always stripped from token names before printing them to error messages.
1314     int InstrScript_tnamerr(char* yyres, const char* yystr) {
1315     if (*yystr == '"') {
1316     int yyn = 0;
1317     char const *yyp = yystr;
1318     for (;;)
1319     switch (*++yyp)
1320     {
1321     /*
1322     case '\'':
1323     case ',':
1324     goto do_not_strip_quotes;
1325    
1326     case '\\':
1327     if (*++yyp != '\\')
1328     goto do_not_strip_quotes;
1329     */
1330     /* Fall through. */
1331     default:
1332     if (yyres)
1333     yyres[yyn] = *yyp;
1334     yyn++;
1335     break;
1336    
1337     case '"':
1338     if (yyres)
1339     yyres[yyn] = '\0';
1340     return yyn;
1341     }
1342 schoenebeck 3034 /*
1343 schoenebeck 3008 do_not_strip_quotes: ;
1344 schoenebeck 3034 */
1345 schoenebeck 3008 }
1346    
1347     if (! yyres)
1348 schoenebeck 3054 return (int) yystrlen (yystr);
1349 schoenebeck 3008
1350 schoenebeck 3054 return int( yystpcpy (yyres, yystr) - yyres );
1351 schoenebeck 3008 }

  ViewVC Help
Powered by ViewVC