}
%union {
+ CYArgument *argument_;
+ CYBoolean *boolean_;
+ CYClause *clause_;
+ CYCatch *catch_;
+ CYDeclaration *declaration_;
+ CYDeclarations *declarations_;
+ CYElement *element_;
CYExpression *expression_;
- CYTokenIdentifier *identifier_;
- CYTokenNumber *number_;
- CYTokenString *string_;
+ CYFalse *false_;
+ CYForInitialiser *for_;
+ CYForInInitialiser *forin_;
+ CYIdentifier *identifier_;
+ CYLiteral *literal_;
+ CYName *name_;
+ CYNull *null_;
+ CYNumber *number_;
+ CYParameter *parameter_;
+ CYProperty *property_;
+ CYSource *source_;
+ CYStatement *statement_;
+ CYString *string_;
+ CYThis *this_;
+ CYTrue *true_;
+ CYWord *word_;
}
%name-prefix "cy"
%token OpenBracket "["
%token CloseBracket "]"
-%token Break "break"
-%token Case "case"
-%token Catch "catch"
-%token Continue "continue"
-%token Default "default"
-%token Delete "delete"
-%token Do "do"
-%token Else "else"
-%token False "false"
-%token Finally "finally"
-%token For "for"
-%token Function "function"
-%token If "if"
-%token In "in"
-%token InstanceOf "instanceof"
-%token New "new"
-%token Null "null"
-%token Return "return"
-%token Switch "switch"
-%token This "this"
-%token Throw "throw"
-%token True "true"
-%token Try "try"
-%token TypeOf "typeof"
-%token Var "var"
-%token Void "void"
-%token While "while"
-%token With "with"
+%token <word_> Break "break"
+%token <word_> Case "case"
+%token <word_> Catch "catch"
+%token <word_> Continue "continue"
+%token <word_> Default "default"
+%token <word_> Delete "delete"
+%token <word_> Do "do"
+%token <word_> Else "else"
+%token <false_> False "false"
+%token <word_> Finally "finally"
+%token <word_> For "for"
+%token <word_> Function "function"
+%token <word_> If "if"
+%token <word_> In "in"
+%token <word_> InstanceOf "instanceof"
+%token <word_> New "new"
+%token <null_> Null "null"
+%token <word_> Return "return"
+%token <word_> Switch "switch"
+%token <this_> This "this"
+%token <word_> Throw "throw"
+%token <true_> True "true"
+%token <word_> Try "try"
+%token <word_> TypeOf "typeof"
+%token <word_> Var "var"
+%token <word_> Void "void"
+%token <word_> While "while"
+%token <word_> With "with"
%token <identifier_> Identifier
%token <number_> NumericLiteral
%token <string_> StringLiteral
+%type <expression_> AdditiveExpression
+%type <argument_> ArgumentList
+%type <argument_> ArgumentList_
+%type <argument_> ArgumentListOpt
+%type <argument_> Arguments
+%type <literal_> ArrayLiteral
+%type <expression_> AssignmentExpression
+%type <expression_> BitwiseANDExpression
+%type <statement_> Block
+%type <boolean_> BooleanLiteral
+%type <expression_> BitwiseORExpression
+%type <expression_> BitwiseXORExpression
+%type <statement_> BreakStatement
+%type <expression_> CallExpression
+%type <clause_> CaseBlock
+%type <clause_> CaseClause
+%type <clause_> CaseClausesOpt
+%type <catch_> CatchOpt
+%type <expression_> ConditionalExpression
+%type <statement_> ContinueStatement
+%type <clause_> DefaultClause
+%type <statement_> DoWhileStatement
+%type <expression_> Element
+%type <element_> ElementList
+%type <element_> ElementList_
+%type <statement_> ElseStatementOpt
+%type <statement_> EmptyStatement
+%type <expression_> EqualityExpression
+%type <expression_> Expression
+%type <expression_> Expression_
+%type <expression_> ExpressionOpt
+%type <statement_> ExpressionStatement
+%type <statement_> FinallyOpt
+%type <statement_> ForStatement
+%type <for_> ForStatementInitialiser
+%type <statement_> ForInStatement
+%type <forin_> ForInStatementInitialiser
+%type <parameter_> FormalParameterList
+%type <parameter_> FormalParameterList_
+%type <source_> FunctionBody
+%type <source_> FunctionDeclaration
+%type <expression_> FunctionExpression
+%type <identifier_> IdentifierOpt
+%type <statement_> IfStatement
+%type <expression_> Initialiser
+%type <expression_> InitialiserOpt
+%type <statement_> IterationStatement
+%type <statement_> LabelledStatement
+%type <expression_> LeftHandSideExpression
+%type <literal_> Literal
+%type <expression_> LogicalANDExpression
+%type <expression_> LogicalORExpression
+%type <expression_> MemberExpression
+%type <expression_> MultiplicativeExpression
+%type <expression_> NewExpression
+%type <null_> NullLiteral
+%type <literal_> ObjectLiteral
+%type <expression_> MessageExpression
+%type <expression_> PostfixExpression
+%type <expression_> PrimaryExpression
+%type <source_> Program
+%type <name_> PropertyName
+%type <property_> PropertyNameAndValueList
+%type <property_> PropertyNameAndValueList_
+%type <property_> PropertyNameAndValueListOpt
+%type <expression_> RelationalExpression
+%type <statement_> ReturnStatement
+%type <argument_> SelectorCall
+%type <argument_> SelectorCall_
+%type <argument_> SelectorList
+%type <expression_> ShiftExpression
+%type <source_> SourceElement
+%type <source_> SourceElements
+%type <statement_> Statement
+%type <statement_> StatementListOpt
+%type <statement_> SwitchStatement
+%type <statement_> ThrowStatement
+%type <statement_> TryStatement
+%type <expression_> UnaryExpression
+%type <declaration_> VariableDeclaration
+%type <declarations_> VariableDeclarationList
+%type <declarations_> VariableDeclarationList_
+%type <statement_> VariableStatement
+%type <argument_> VariadicCall
+%type <statement_> WhileStatement
+%type <statement_> WithStatement
+%type <word_> Word
+%type <word_> WordOpt
+
%%
%start Program;
WordOpt
- : Word
- |
+ : Word { $$ = $1; }
+ | { $$ = NULL; }
;
Word
- : Identifier
- | "break"
- | "case"
- | "catch"
- | "continue"
- | "default"
- | "delete"
- | "do"
- | "else"
- | "false"
- | "finally"
- | "for"
- | "function"
- | "if"
- | "in"
- | "instanceof"
- | "new"
- | "null"
- | "return"
- | "switch"
- | "this"
- | "throw"
- | "true"
- | "try"
- | "typeof"
- | "var"
- | "void"
- | "while"
- | "with"
+ : Identifier { $$ = $1; }
+ | "break" { $$ = $1; }
+ | "case" { $$ = $1; }
+ | "catch" { $$ = $1; }
+ | "continue" { $$ = $1; }
+ | "default" { $$ = $1; }
+ | "delete" { $$ = $1; }
+ | "do" { $$ = $1; }
+ | "else" { $$ = $1; }
+ | "false" { $$ = $1; }
+ | "finally" { $$ = $1; }
+ | "for" { $$ = $1; }
+ | "function" { $$ = $1; }
+ | "if" { $$ = $1; }
+ | "in" { $$ = $1; }
+ | "instanceof" { $$ = $1; }
+ | "new" { $$ = $1; }
+ | "null" { $$ = $1; }
+ | "return" { $$ = $1; }
+ | "switch" { $$ = $1; }
+ | "this" { $$ = $1; }
+ | "throw" { $$ = $1; }
+ | "true" { $$ = $1; }
+ | "try" { $$ = $1; }
+ | "typeof" { $$ = $1; }
+ | "var" { $$ = $1; }
+ | "void" { $$ = $1; }
+ | "while" { $$ = $1; }
+ | "with" { $$ = $1; }
;
IdentifierOpt
- : Identifier
- |
+ : Identifier { $$ = $1; }
+ | { $$ = NULL; }
;
Literal
- : NullLiteral
- | BooleanLiteral
- | NumericLiteral
- | StringLiteral
+ : NullLiteral { $$ = $1; }
+ | BooleanLiteral { $$ = $1; }
+ | NumericLiteral { $$ = $1; }
+ | StringLiteral { $$ = $1; }
;
NullLiteral
- : "null"
+ : "null" { $$ = $1; }
;
BooleanLiteral
- : "true"
- | "false"
+ : "true" { $$ = $1; }
+ | "false" { $$ = $1; }
;
/* Objective-C Extensions {{{ */
VariadicCall
- : "," AssignmentExpression VariadicCall
- |
+ : "," AssignmentExpression VariadicCall { $$ = new CYArgument(NULL, $2, $3); }
+ | { $$ = NULL; }
;
SelectorCall_
- : SelectorCall
- | VariadicCall
+ : SelectorCall { $$ = $1; }
+ | VariadicCall { $$ = $1; }
;
SelectorCall
- : WordOpt ":" AssignmentExpression SelectorCall_
+ : WordOpt ":" AssignmentExpression SelectorCall_ { $$ = new CYArgument($1 ?: new CYBlank(), $3, $4); }
;
SelectorList
- : SelectorCall
- | Word
+ : SelectorCall { $$ = $1; }
+ | Word { $$ = new CYArgument($1, NULL); }
;
-ObjectiveCall
- : "[" AssignmentExpression SelectorList "]"
+MessageExpression
+ : "[" AssignmentExpression SelectorList "]" { $$ = new CYMessage($2, $3); }
;
/* }}} */
/* 11.1 Primary Expressions {{{ */
PrimaryExpression
- : "this"
- | Identifier
- | Literal
- | ArrayLiteral
- | ObjectLiteral
- | "(" Expression ")"
- | ObjectiveCall
+ : "this" { $$ = $1; }
+ | Identifier { $$ = new CYVariable($1); }
+ | Literal { $$ = $1; }
+ | ArrayLiteral { $$ = $1; }
+ | ObjectLiteral { $$ = $1; }
+ | "(" Expression ")" { $$ = $2; }
+ | MessageExpression { $$ = $1; }
;
/* }}} */
/* 11.1.4 Array Initialiser {{{ */
ArrayLiteral
- : "[" ElementList "]"
+ : "[" ElementList "]" { $$ = $2; }
;
Element
- : AssignmentExpression
- |
+ : AssignmentExpression { $$ = $1; }
+ | { $$ = NULL; }
;
ElementList_
- : "," ElementList
- |
+ : "," ElementList { $$ = $2; }
+ | { $$ = NULL; }
;
ElementList
- : Element ElementList_
+ : Element ElementList_ { $$ = new CYElement($1, $2); }
;
/* }}} */
/* 11.1.5 Object Initialiser {{{ */
ObjectLiteral
- : "{" PropertyNameAndValueListOpt "}"
+ : "{" PropertyNameAndValueListOpt "}" { $$ = $2; }
;
PropertyNameAndValueList_
- : "," PropertyNameAndValueList
- |
+ : "," PropertyNameAndValueList { $$ = $2; }
+ | { $$ = NULL; }
;
PropertyNameAndValueListOpt
- : PropertyNameAndValueList
- |
+ : PropertyNameAndValueList { $$ = $1; }
+ | { $$ = NULL; }
;
PropertyNameAndValueList
- : PropertyName ":" AssignmentExpression PropertyNameAndValueList_
+ : PropertyName ":" AssignmentExpression PropertyNameAndValueList_ { $$ = new CYProperty($1, $3, $4); }
;
PropertyName
- : Identifier
- | StringLiteral
- | NumericLiteral
+ : Identifier { $$ = $1; }
+ | StringLiteral { $$ = $1; }
+ | NumericLiteral { $$ = $1; }
;
/* }}} */
MemberExpression
- : PrimaryExpression
- | FunctionExpression
- | MemberExpression "[" Expression "]"
- | MemberExpression "." Identifier
- | "new" MemberExpression Arguments
+ : PrimaryExpression { $$ = $1; }
+ | FunctionExpression { $$ = $1; }
+ | MemberExpression "[" Expression "]" { $$ = new CYMember($1, $3); }
+ | MemberExpression "." Identifier { $$ = new CYMember($1, new CYString($3)); }
+ | "new" MemberExpression Arguments { $$ = new CYNew($2, $3); }
;
NewExpression
- : MemberExpression
- | "new" NewExpression
+ : MemberExpression { $$ = $1; }
+ | "new" NewExpression { $$ = new CYNew($2, NULL); }
;
CallExpression
- : MemberExpression Arguments
- | CallExpression Arguments
- | CallExpression "[" Expression "]"
- | CallExpression "." Identifier
+ : MemberExpression Arguments { $$ = new CYCall($1, $2); }
+ | CallExpression Arguments { $$ = new CYCall($1, $2); }
+ | CallExpression "[" Expression "]" { $$ = new CYMember($1, $3); }
+ | CallExpression "." Identifier { $$ = new CYMember($1, new CYString($3)); }
;
ArgumentList_
- : "," ArgumentList
- |
+ : "," ArgumentList { $$ = $2; }
+ | { $$ = NULL; }
;
ArgumentListOpt
- : ArgumentList
- |
+ : ArgumentList { $$ = $1; }
+ | { $$ = NULL; }
;
ArgumentList
- : AssignmentExpression ArgumentList_
+ : AssignmentExpression ArgumentList_ { $$ = new CYArgument(NULL, $1, $2); }
;
Arguments
- : "(" ArgumentListOpt ")"
+ : "(" ArgumentListOpt ")" { $$ = $2; }
;
LeftHandSideExpression
- : NewExpression
- | CallExpression
+ : NewExpression { $$ = $1; }
+ | CallExpression { $$ = $1; }
;
PostfixExpression
- : LeftHandSideExpression
- | LeftHandSideExpression "++"
- | LeftHandSideExpression "--"
+ : LeftHandSideExpression { $$ = $1; }
+ | LeftHandSideExpression "++" { $$ = new CYPostIncrement($1); }
+ | LeftHandSideExpression "--" { $$ = new CYPostDecrement($1); }
;
UnaryExpression
- : PostfixExpression
- | "delete" UnaryExpression
- | "void" UnaryExpression
- | "typeof" UnaryExpression
- | "++" UnaryExpression
- | "--" UnaryExpression
- | "+" UnaryExpression
- | "-" UnaryExpression
- | "~" UnaryExpression
- | "!" UnaryExpression
- | "*" UnaryExpression
- | "&" UnaryExpression
+ : PostfixExpression { $$ = $1; }
+ | "delete" UnaryExpression { $$ = new CYDelete($2); }
+ | "void" UnaryExpression { $$ = new CYVoid($2); }
+ | "typeof" UnaryExpression { $$ = new CYTypeOf($2); }
+ | "++" UnaryExpression { $$ = new CYPreIncrement($2); }
+ | "--" UnaryExpression { $$ = new CYPreDecrement($2); }
+ | "+" UnaryExpression { $$ = $2; }
+ | "-" UnaryExpression { $$ = new CYNegate($2); }
+ | "~" UnaryExpression { $$ = new CYBitwiseNot($2); }
+ | "!" UnaryExpression { $$ = new CYLogicalNot($2); }
+ | "*" UnaryExpression { $$ = new CYIndirect($2); }
+ | "&" UnaryExpression { $$ = new CYAddressOf($2); }
;
MultiplicativeExpression
- : UnaryExpression
- | MultiplicativeExpression "*" UnaryExpression
- | MultiplicativeExpression "/" UnaryExpression
- | MultiplicativeExpression "%" UnaryExpression
+ : UnaryExpression { $$ = $1; }
+ | MultiplicativeExpression "*" UnaryExpression { $$ = new CYMultiply($1, $3); }
+ | MultiplicativeExpression "/" UnaryExpression { $$ = new CYDivide($1, $3); }
+ | MultiplicativeExpression "%" UnaryExpression { $$ = new CYModulus($1, $3); }
;
AdditiveExpression
- : MultiplicativeExpression
- | AdditiveExpression "+" MultiplicativeExpression
- | AdditiveExpression "-" MultiplicativeExpression
+ : MultiplicativeExpression { $$ = $1; }
+ | AdditiveExpression "+" MultiplicativeExpression { $$ = new CYAdd($1, $3); }
+ | AdditiveExpression "-" MultiplicativeExpression { $$ = new CYSubtract($1, $3); }
;
ShiftExpression
- : AdditiveExpression
- | ShiftExpression "<<" AdditiveExpression
- | ShiftExpression ">>" AdditiveExpression
- | ShiftExpression ">>>" AdditiveExpression
+ : AdditiveExpression { $$ = $1; }
+ | ShiftExpression "<<" AdditiveExpression { $$ = new CYShiftLeft($1, $3); }
+ | ShiftExpression ">>" AdditiveExpression { $$ = new CYShiftRightSigned($1, $3); }
+ | ShiftExpression ">>>" AdditiveExpression { $$ = new CYShiftRightUnsigned($1, $3); }
;
RelationalExpression
- : ShiftExpression
- | RelationalExpression "<" ShiftExpression
- | RelationalExpression ">" ShiftExpression
- | RelationalExpression "<=" ShiftExpression
- | RelationalExpression ">=" ShiftExpression
- | RelationalExpression "instanceof" ShiftExpression
- | RelationalExpression "in" ShiftExpression
+ : ShiftExpression { $$ = $1; }
+ | RelationalExpression "<" ShiftExpression { $$ = new CYLess($1, $3); }
+ | RelationalExpression ">" ShiftExpression { $$ = new CYGreater($1, $3); }
+ | RelationalExpression "<=" ShiftExpression { $$ = new CYLessOrEqual($1, $3); }
+ | RelationalExpression ">=" ShiftExpression { $$ = new CYGreaterOrEqual($1, $3); }
+ | RelationalExpression "instanceof" ShiftExpression { $$ = new CYInstanceOf($1, $3); }
+ | RelationalExpression "in" ShiftExpression { $$ = new CYIn($1, $3); }
;
EqualityExpression
- : RelationalExpression
- | EqualityExpression "==" RelationalExpression
- | EqualityExpression "!=" RelationalExpression
- | EqualityExpression "===" RelationalExpression
- | EqualityExpression "!==" RelationalExpression
+ : RelationalExpression { $$ = $1; }
+ | EqualityExpression "==" RelationalExpression { $$ = new CYEqual($1, $3); }
+ | EqualityExpression "!=" RelationalExpression { $$ = new CYNotEqual($1, $3); }
+ | EqualityExpression "===" RelationalExpression { $$ = new CYIdentical($1, $3); }
+ | EqualityExpression "!==" RelationalExpression { $$ = new CYNotIdentical($1, $3); }
;
BitwiseANDExpression
- : EqualityExpression
- | BitwiseANDExpression "&" EqualityExpression
+ : EqualityExpression { $$ = $1; }
+ | BitwiseANDExpression "&" EqualityExpression { $$ = new CYBitwiseAnd($1, $3); }
;
BitwiseXORExpression
- : BitwiseANDExpression
- | BitwiseXORExpression "^" BitwiseANDExpression
+ : BitwiseANDExpression { $$ = $1; }
+ | BitwiseXORExpression "^" BitwiseANDExpression { $$ = new CYBitwiseXOr($1, $3); }
;
BitwiseORExpression
- : BitwiseXORExpression
- | BitwiseORExpression "|" BitwiseXORExpression
+ : BitwiseXORExpression { $$ = $1; }
+ | BitwiseORExpression "|" BitwiseXORExpression { $$ = new CYBitwiseOr($1, $3); }
;
LogicalANDExpression
- : BitwiseORExpression
- | LogicalANDExpression "&&" BitwiseORExpression
+ : BitwiseORExpression { $$ = $1; }
+ | LogicalANDExpression "&&" BitwiseORExpression { $$ = new CYLogicalAnd($1, $3); }
;
LogicalORExpression
- : LogicalANDExpression
- | LogicalORExpression "||" LogicalANDExpression
+ : LogicalANDExpression { $$ = $1; }
+ | LogicalORExpression "||" LogicalANDExpression { $$ = new CYLogicalOr($1, $3); }
;
ConditionalExpression
- : LogicalORExpression
- | LogicalORExpression "?" AssignmentExpression ":" AssignmentExpression
+ : LogicalORExpression { $$ = $1; }
+ | LogicalORExpression "?" AssignmentExpression ":" AssignmentExpression { $$ = new CYCondition($1, $3, $5); }
;
AssignmentExpression
- : ConditionalExpression
- | LeftHandSideExpression AssignmentOperator AssignmentExpression
- ;
-
-AssignmentOperator
- : "="
- | "*="
- | "/="
- | "%="
- | "+="
- | "-="
- | "<<="
- | ">>="
- | ">>>="
- | "&="
- | "^="
- | "|="
+ : ConditionalExpression { $$ = $1; }
+ | LeftHandSideExpression "=" AssignmentExpression { $$ = new CYAssign($1, $3); }
+ | LeftHandSideExpression "*=" AssignmentExpression { $$ = new CYMultiplyAssign($1, $3); }
+ | LeftHandSideExpression "/=" AssignmentExpression { $$ = new CYDivideAssign($1, $3); }
+ | LeftHandSideExpression "%=" AssignmentExpression { $$ = new CYModulusAssign($1, $3); }
+ | LeftHandSideExpression "+=" AssignmentExpression { $$ = new CYAddAssign($1, $3); }
+ | LeftHandSideExpression "-=" AssignmentExpression { $$ = new CYSubtractAssign($1, $3); }
+ | LeftHandSideExpression "<<=" AssignmentExpression { $$ = new CYShiftLeftAssign($1, $3); }
+ | LeftHandSideExpression ">>=" AssignmentExpression { $$ = new CYShiftRightSignedAssign($1, $3); }
+ | LeftHandSideExpression ">>>=" AssignmentExpression { $$ = new CYShiftRightUnsignedAssign($1, $3); }
+ | LeftHandSideExpression "&=" AssignmentExpression { $$ = new CYBitwiseAndAssign($1, $3); }
+ | LeftHandSideExpression "^=" AssignmentExpression { $$ = new CYBitwiseXOrAssign($1, $3); }
+ | LeftHandSideExpression "|=" AssignmentExpression { $$ = new CYBitwiseOrAssign($1, $3); }
;
Expression_
- : "," Expression
- |
+ : "," Expression { $$ = $2; }
+ | { $$ = NULL; }
;
ExpressionOpt
- : Expression
- |
+ : Expression { $$ = $1; }
+ | { $$ = NULL; }
;
Expression
- : AssignmentExpression Expression_
+ : AssignmentExpression Expression_ { $1->SetNext($2); $$ = $1; }
;
Statement
- : Block
- | VariableStatement
- | EmptyStatement
- | ExpressionStatement
- | IfStatement
- | IterationStatement
- | ContinueStatement
- | BreakStatement
- | ReturnStatement
- | WithStatement
- | LabelledStatement
- | SwitchStatement
- | ThrowStatement
- | TryStatement
+ : Block { $$ = $1; }
+ | VariableStatement { $$ = $1; }
+ | EmptyStatement { $$ = $1; }
+ | ExpressionStatement { $$ = $1; }
+ | IfStatement { $$ = $1; }
+ | IterationStatement { $$ = $1; }
+ | ContinueStatement { $$ = $1; }
+ | BreakStatement { $$ = $1; }
+ | ReturnStatement { $$ = $1; }
+ | WithStatement { $$ = $1; }
+ | LabelledStatement { $$ = $1; }
+ | SwitchStatement { $$ = $1; }
+ | ThrowStatement { $$ = $1; }
+ | TryStatement { $$ = $1; }
;
Block
- : "{" StatementListOpt "}"
+ : "{" StatementListOpt "}" { $$ = $2 ?: new CYEmpty(); }
;
StatementListOpt
- : Statement StatementListOpt
- |
+ : Statement StatementListOpt { $1->SetNext($2); $$ = $1; }
+ | { $$ = NULL; }
;
VariableStatement
- : "var" VariableDeclarationList ";"
+ : "var" VariableDeclarationList ";" { $$ = $2; }
;
VariableDeclarationList_
- : "," VariableDeclarationList
- |
+ : "," VariableDeclarationList { $$ = $2; }
+ | { $$ = NULL; }
;
VariableDeclarationList
- : VariableDeclaration VariableDeclarationList_
+ : VariableDeclaration VariableDeclarationList_ { $$ = new CYDeclarations($1, $2); }
;
VariableDeclaration
- : Identifier InitialiserOpt
+ : Identifier InitialiserOpt { $$ = new CYDeclaration($1, $2); }
;
InitialiserOpt
- : Initialiser
- |
+ : Initialiser { $$ = $1; }
+ | { $$ = NULL; }
;
Initialiser
- : "=" AssignmentExpression
+ : "=" AssignmentExpression { $$ = $2; }
;
EmptyStatement
- : ";"
+ : ";" { $$ = new CYEmpty(); }
;
ExpressionStatement
- : Expression ";"
+ : Expression ";" { $$ = $1; }
;
ElseStatementOpt
- : "else" Statement
- |
+ : "else" Statement { $$ = $2; }
+ | { $$ = NULL; }
;
IfStatement
- : "if" "(" Expression ")" Statement ElseStatementOpt
+ : "if" "(" Expression ")" Statement ElseStatementOpt { $$ = new CYIf($3, $5, $6); }
;
IterationStatement
- : DoWhileStatement
- | WhileStatement
- | ForStatement
- | ForInStatement
+ : DoWhileStatement { $$ = $1; }
+ | WhileStatement { $$ = $1; }
+ | ForStatement { $$ = $1; }
+ | ForInStatement { $$ = $1; }
;
DoWhileStatement
- : "do" Statement "while" "(" Expression ")" ";"
+ : "do" Statement "while" "(" Expression ")" ";" { $$ = new CYDoWhile($5, $2); }
;
WhileStatement
- : "while" "(" Expression ")" Statement
+ : "while" "(" Expression ")" Statement { $$ = new CYWhile($3, $5); }
;
ForStatement
- : "for" "(" ForStatementInitialiser ";" ExpressionOpt ";" ExpressionOpt ")" Statement
+ : "for" "(" ForStatementInitialiser ";" ExpressionOpt ";" ExpressionOpt ")" Statement { $$ = new CYFor($3, $5, $7, $9); }
;
ForStatementInitialiser
- : ExpressionOpt
- | "var" VariableDeclarationList
+ : ExpressionOpt { $$ = $1; }
+ | "var" VariableDeclarationList { $$ = $2; }
;
ForInStatement
- : "for" "(" ForInStatementInitialiser "in" Expression ")" Statement
+ : "for" "(" ForInStatementInitialiser "in" Expression ")" Statement { $$ = new CYForIn($3, $5, $7); }
;
ForInStatementInitialiser
- : LeftHandSideExpression
- | "var" VariableDeclaration
+ : LeftHandSideExpression { $$ = $1; }
+ | "var" VariableDeclaration { $$ = $2; }
;
ContinueStatement
- : "continue" IdentifierOpt ";"
+ : "continue" IdentifierOpt ";" { $$ = new CYContinue($2); }
;
BreakStatement
- : "break" IdentifierOpt ";"
+ : "break" IdentifierOpt ";" { $$ = new CYBreak($2); }
;
ReturnStatement
- : "return" ExpressionOpt ";"
+ : "return" ExpressionOpt ";" { $$ = new CYReturn($2); }
;
WithStatement
- : "with" "(" Expression ")" Statement
+ : "with" "(" Expression ")" Statement { $$ = new CYWith($3, $5); }
;
SwitchStatement
- : "switch" "(" Expression ")" CaseBlock
+ : "switch" "(" Expression ")" CaseBlock { $$ = new CYSwitch($3, $5); }
;
CaseBlock
- : "{" CaseClausesOpt "}"
+ : "{" CaseClausesOpt "}" { $$ = $2; }
;
CaseClausesOpt
- : CaseClause CaseClausesOpt
- | DefaultClause CaseClausesOpt
- |
+ : CaseClause CaseClausesOpt { $1->SetNext($2); $$ = $1; }
+ | DefaultClause CaseClausesOpt { $1->SetNext($2); $$ = $1; }
+ | { $$ = NULL; }
;
CaseClause
- : "case" Expression ":" StatementListOpt
+ : "case" Expression ":" StatementListOpt { $$ = new CYClause($2, $4); }
;
DefaultClause
- : "default" ":" StatementListOpt
+ : "default" ":" StatementListOpt { $$ = new CYClause(NULL, $3); }
;
LabelledStatement
- : Identifier ":" Statement
+ : Identifier ":" Statement { $3->AddLabel($1); $$ = $3; }
;
ThrowStatement
- : "throw" Expression ";"
+ : "throw" Expression ";" { $$ = new CYThrow($2); }
;
TryStatement
- : "try" Block CatchOpt FinallyOpt
+ : "try" Block CatchOpt FinallyOpt { $$ = new CYTry($2, $3, $4); }
;
CatchOpt
- : "catch" "(" Identifier ")" Block
- |
+ : "catch" "(" Identifier ")" Block { $$ = new CYCatch($3, $5); }
+ | { $$ = NULL; }
;
FinallyOpt
- : "finally" Block
- |
+ : "finally" Block { $$ = $2; }
+ | { $$ = NULL; }
;
FunctionDeclaration
- : "function" Identifier "(" FormalParameterList ")" "{" FunctionBody "}"
+ : "function" Identifier "(" FormalParameterList ")" "{" FunctionBody "}" { $$ = new CYFunction($2, $4, $7); }
;
FunctionExpression
- : "function" IdentifierOpt "(" FormalParameterList ")" "{" FunctionBody "}"
+ : "function" IdentifierOpt "(" FormalParameterList ")" "{" FunctionBody "}" { $$ = new CYLambda($2, $4, $7); }
;
FormalParameterList_
- : "," FormalParameterList
- |
+ : "," FormalParameterList { $$ = $2; }
+ | { $$ = NULL; }
;
FormalParameterList
- : Identifier FormalParameterList_
- |
+ : Identifier FormalParameterList_ { $$ = new CYParameter($1, $2); }
+ | { $$ = NULL; }
;
FunctionBody
- : SourceElements
+ : SourceElements { $$ = $1; }
;
Program
- : SourceElements
+ : SourceElements { $$ = $1; }
;
SourceElements
- : SourceElement SourceElements
- |
+ : SourceElement SourceElements { $1->SetNext($2); $$ = $1; }
+ | { $$ = NULL; }
;
SourceElement
- : Statement
- | FunctionDeclaration
+ : Statement { $$ = $1; }
+ | FunctionDeclaration { $$ = $1; }
;
%%
}
// XXX: this is not a safe handle
-class CYString {
+class CYJSString {
private:
JSStringRef string_;
public:
template <typename Arg0_>
- CYString(Arg0_ arg0) {
+ CYJSString(Arg0_ arg0) {
string_ = CYCopyJSString(arg0);
}
template <typename Arg0_, typename Arg1_>
- CYString(Arg0_ arg0, Arg1_ arg1) {
+ CYJSString(Arg0_ arg0, Arg1_ arg1) {
string_ = CYCopyJSString(arg0, arg1);
}
- ~CYString() {
+ ~CYJSString() {
JSStringRelease(string_);
}
}
CFStringRef CYCopyCFString(JSContextRef context, JSValueRef value) {
- return CYCopyCFString(CYString(context, value));
+ return CYCopyCFString(CYJSString(context, value));
}
double CYCastDouble(JSContextRef context, JSValueRef value) {
- (id) objectForKey:(id)key {
JSValueRef exception(NULL);
- JSValueRef value(JSObjectGetProperty(context_, object_, CYString(key), &exception));
+ JSValueRef value(JSObjectGetProperty(context_, object_, CYJSString(key), &exception));
CYThrow(context_, exception);
return CYCastNSObject(context_, value);
}
- (void) setObject:(id)object forKey:(id)key {
JSValueRef exception(NULL);
- JSObjectSetProperty(context_, object_, CYString(key), CYCastJSValue(context_, object), kJSPropertyAttributeNone, &exception);
+ JSObjectSetProperty(context_, object_, CYJSString(key), CYCastJSValue(context_, object), kJSPropertyAttributeNone, &exception);
CYThrow(context_, exception);
}
- (void) removeObjectForKey:(id)key {
JSValueRef exception(NULL);
// XXX: this returns a bool... throw exception, or ignore?
- JSObjectDeleteProperty(context_, object_, CYString(key), &exception);
+ JSObjectDeleteProperty(context_, object_, CYJSString(key), &exception);
CYThrow(context_, exception);
}
void CYSetProperty(JSContextRef context, JSObjectRef object, const char *name, JSValueRef value) {
JSValueRef exception(NULL);
- JSObjectSetProperty(context, object, CYString(name), value, kJSPropertyAttributeNone, &exception);
+ JSObjectSetProperty(context, object, CYJSString(name), value, kJSPropertyAttributeNone, &exception);
CYThrow(context, exception);
}
}
char *CYPoolCString(apr_pool_t *pool, JSContextRef context, JSValueRef value) {
- return CYPoolCString(pool, CYString(context, value));
+ return CYPoolCString(pool, CYJSString(context, value));
}
// XXX: this macro is unhygenic
case sig::string_P: {
if (char *utf8 = *reinterpret_cast<char **>(data))
- value = JSValueMakeString(context, CYString(utf8));
+ value = JSValueMakeString(context, CYJSString(utf8));
else goto null;
} break;
if (NSMutableArray *entry = [Bridge_ objectForKey:name])
switch ([[entry objectAtIndex:0] intValue]) {
case 0:
- return JSEvaluateScript(JSGetContext(), CYString([entry objectAtIndex:1]), NULL, NULL, 0, NULL);
+ return JSEvaluateScript(JSGetContext(), CYJSString([entry objectAtIndex:1]), NULL, NULL, 0, NULL);
case 1:
return CYMakeFunction(context, [name cy$symbol], [[entry objectAtIndex:1] UTF8String]);
case 2:
CYSetProperty(context, global, "ffi", JSObjectMakeConstructor(context, Functor_, &ffi));
- CYSetProperty(context, global, "objc_msgSend", JSObjectMakeFunctionWithCallback(context, CYString("objc_msgSend"), &$objc_msgSend));
+ CYSetProperty(context, global, "objc_msgSend", JSObjectMakeFunctionWithCallback(context, CYJSString("objc_msgSend"), &$objc_msgSend));
Bridge_ = [[NSMutableDictionary dictionaryWithContentsOfFile:@"/usr/lib/libcycript.plist"] retain];
length_ = JSStringCreateWithUTF8CString("length");
JSValueRef exception(NULL);
- JSValueRef value(JSObjectGetProperty(JSGetContext(), global, CYString("Array"), &exception));
+ JSValueRef value(JSObjectGetProperty(JSGetContext(), global, CYJSString("Array"), &exception));
CYThrow(context, exception);
Array_ = JSValueToObject(JSGetContext(), value, &exception);
CYThrow(context, exception);
#ifndef CYPARSER_HPP
#define CYPARSER_HPP
+#include <cstdlib>
+
class CYParser {
public:
void *scanner_;
~CYParser();
};
-struct CYExpression {
+struct CYSource {
+ CYSource *next_;
+
+ void SetNext(CYSource *next) {
+ next_ = next;
+ }
+};
+
+struct CYName {
+ virtual const char *Name() const = 0;
};
struct CYToken {
virtual const char *Text() const = 0;
};
-struct CYTokenLiteral :
- CYExpression,
- virtual CYToken
+struct CYWord :
+ virtual CYToken,
+ CYName
{
+ const char *word_;
+
+ CYWord(const char *word) :
+ word_(word)
+ {
+ }
+
+ virtual const char *Text() const {
+ return word_;
+ }
+
+ virtual const char *Name() const {
+ return Text();
+ }
};
-struct CYTokenString :
- CYTokenLiteral
+struct CYIdentifier :
+ CYWord
{
+ const char *word_;
+
+ virtual const char *Text() const {
+ return word_;
+ }
};
-struct CYTokenNumber :
- CYTokenLiteral
+struct CYLabel {
+ CYIdentifier *identifier_;
+ CYLabel *next_;
+
+ CYLabel(CYIdentifier *identifier, CYLabel *next) :
+ identifier_(identifier),
+ next_(next)
+ {
+ }
+};
+
+struct CYStatement :
+ CYSource
{
+ CYLabel *label_;
+
+ void AddLabel(CYIdentifier *identifier) {
+ label_ = new CYLabel(identifier, label_);
+ }
+};
+
+struct CYForInitialiser {
+};
+
+struct CYForInInitialiser {
};
-struct CYTokenWord :
- virtual CYToken
+struct CYExpression :
+ CYStatement,
+ CYForInitialiser,
+ CYForInInitialiser
{
};
-struct CYTokenIdentifier :
- CYExpression,
- CYTokenWord
+struct CYLiteral :
+ CYExpression
{
- const char *word_;
+};
- virtual const char *Text() const {
- return word_;
+struct CYString :
+ CYLiteral,
+ CYName
+{
+ const char *value_;
+
+ CYString(const char *value) :
+ value_(value)
+ {
+ }
+
+ CYString(const CYIdentifier *identifier) :
+ value_(identifier->Text())
+ {
+ }
+
+ const char *String() const {
+ return value_;
+ }
+
+ virtual const char *Name() const {
+ return String();
}
};
-struct CYExpressionPrefix :
+struct CYNumber :
+ virtual CYToken,
+ CYLiteral,
+ CYName
+{
+ double Number() const {
+ throw;
+ }
+
+ virtual const char *Name() const {
+ throw;
+ }
+};
+
+struct CYNull :
+ CYWord,
+ CYLiteral
+{
+ CYNull() :
+ CYWord("null")
+ {
+ }
+};
+
+struct CYThis :
+ CYWord,
+ CYExpression
+{
+ CYThis() :
+ CYWord("this")
+ {
+ }
+};
+
+struct CYBoolean :
+ CYLiteral
+{
+};
+
+struct CYFalse :
+ CYWord,
+ CYBoolean
+{
+ CYFalse() :
+ CYWord("false")
+ {
+ }
+};
+
+struct CYTrue :
+ CYWord,
+ CYBoolean
+{
+ CYTrue() :
+ CYWord("true")
+ {
+ }
+};
+
+struct CYVariable :
+ CYExpression
+{
+ CYIdentifier *name_;
+
+ CYVariable(CYIdentifier *name) :
+ name_(name)
+ {
+ }
+};
+
+struct CYPrefix :
CYExpression
{
CYExpression *rhs_;
- CYExpressionPrefix(CYExpression *rhs) :
+ CYPrefix(CYExpression *rhs) :
rhs_(rhs)
{
}
};
-struct CYExpressionInfix :
+struct CYInfix :
CYExpression
{
CYExpression *lhs_;
CYExpression *rhs_;
- CYExpressionInfix(CYExpression *lhs, CYExpression *rhs) :
+ CYInfix(CYExpression *lhs, CYExpression *rhs) :
lhs_(lhs),
rhs_(rhs)
{
}
};
-struct CYExpressionPostfix :
+struct CYPostfix :
CYExpression
{
CYExpression *lhs_;
- CYExpressionPostfix(CYExpression *lhs) :
+ CYPostfix(CYExpression *lhs) :
lhs_(lhs)
{
}
};
-struct CYExpressionAssignment :
+struct CYAssignment :
+ CYInfix
+{
+ CYAssignment(CYExpression *lhs, CYExpression *rhs) :
+ CYInfix(lhs, rhs)
+ {
+ }
+};
+
+struct CYArgument {
+ CYWord *name_;
+ CYExpression *value_;
+ CYArgument *next_;
+
+ CYArgument(CYWord *name, CYExpression *value, CYArgument *next = NULL) :
+ name_(name),
+ value_(value),
+ next_(next)
+ {
+ }
+};
+
+struct CYBlank :
+ public CYWord
+{
+ CYBlank() :
+ CYWord("")
+ {
+ }
+};
+
+struct CYClause {
+ CYExpression *case_;
+ CYStatement *code_;
+ CYClause *next_;
+
+ CYClause(CYExpression *_case, CYStatement *code) :
+ case_(_case),
+ code_(code)
+ {
+ }
+
+ void SetNext(CYClause *next) {
+ next_ = next;
+ }
+};
+
+struct CYElement :
+ CYLiteral
+{
+ CYExpression *value_;
+ CYElement *next_;
+
+ CYElement(CYExpression *value, CYElement *next) :
+ value_(value),
+ next_(next)
+ {
+ }
+};
+
+struct CYDeclaration :
+ CYForInInitialiser
+{
+ CYIdentifier *identifier_;
+ CYExpression *initialiser_;
+
+ CYDeclaration(CYIdentifier *identifier, CYExpression *initialiser) :
+ identifier_(identifier),
+ initialiser_(initialiser)
+ {
+ }
+};
+
+struct CYDeclarations :
+ CYStatement,
+ CYForInitialiser
+{
+ CYDeclaration *declaration_;
+ CYDeclarations *next_;
+
+ CYDeclarations(CYDeclaration *declaration, CYDeclarations *next) :
+ declaration_(declaration),
+ next_(next)
+ {
+ }
+};
+
+struct CYParameter {
+ CYIdentifier *name_;
+ CYParameter *next_;
+
+ CYParameter(CYIdentifier *name, CYParameter *next) :
+ name_(name),
+ next_(next)
+ {
+ }
+};
+
+struct CYFor :
+ CYStatement
+{
+ CYForInitialiser *initialiser_;
+ CYExpression *test_;
+ CYExpression *increment_;
+ CYStatement *code_;
+
+ CYFor(CYForInitialiser *initialiser, CYExpression *test, CYExpression *increment, CYStatement *code) :
+ initialiser_(initialiser),
+ test_(test),
+ increment_(increment),
+ code_(code)
+ {
+ }
+};
+
+struct CYForIn :
+ CYStatement
+{
+ CYForInInitialiser *initialiser_;
+ CYExpression *set_;
+ CYStatement *code_;
+
+ CYForIn(CYForInInitialiser *initialiser, CYExpression *set, CYStatement *code) :
+ initialiser_(initialiser),
+ set_(set),
+ code_(code)
+ {
+ }
+};
+
+struct CYProperty :
+ CYLiteral
+{
+ CYName *name_;
+ CYExpression *value_;
+ CYProperty *next_;
+
+ CYProperty(CYName *name, CYExpression *value, CYProperty *next) :
+ name_(name),
+ value_(value),
+ next_(next)
+ {
+ }
+};
+
+struct CYCatch {
+ CYIdentifier *name_;
+ CYStatement *code_;
+
+ CYCatch(CYIdentifier *name, CYStatement *code) :
+ name_(name),
+ code_(code)
+ {
+ }
+};
+
+struct CYMessage :
CYExpression
{
- CYExpression *lhs_;
- CYExpression *rhs_;
+ CYExpression *self_;
+ CYArgument *arguments_;
- CYExpressionAssignment(CYExpression *lhs, CYExpression *rhs) :
- lhs_(lhs),
- rhs_(rhs)
+ CYMessage(CYExpression *self, CYArgument *arguments) :
+ self_(self),
+ arguments_(arguments)
{
}
};
+struct CYMember :
+ CYExpression
+{
+ CYExpression *object_;
+ CYExpression *property_;
+
+ CYMember(CYExpression *object, CYExpression *property) :
+ object_(object),
+ property_(property)
+ {
+ }
+};
+
+struct CYNew :
+ CYExpression
+{
+ CYExpression *constructor_;
+ CYArgument *arguments_;
+
+ CYNew(CYExpression *constructor, CYArgument *arguments) :
+ constructor_(constructor),
+ arguments_(arguments)
+ {
+ }
+};
+
+struct CYCall :
+ CYExpression
+{
+ CYExpression *function_;
+ CYArgument *arguments_;
+
+ CYCall(CYExpression *function, CYArgument *arguments) :
+ function_(function),
+ arguments_(arguments)
+ {
+ }
+};
+
+struct CYIf :
+ CYStatement
+{
+ CYExpression *test_;
+ CYStatement *true_;
+ CYStatement *false_;
+
+ CYIf(CYExpression *test, CYStatement *_true, CYStatement *_false) :
+ test_(test),
+ true_(_true),
+ false_(_false)
+ {
+ }
+};
+
+struct CYDoWhile :
+ CYStatement
+{
+ CYExpression *test_;
+ CYStatement *code_;
+
+ CYDoWhile(CYExpression *test, CYStatement *code) :
+ test_(test),
+ code_(code)
+ {
+ }
+};
+
+struct CYWhile :
+ CYStatement
+{
+ CYExpression *test_;
+ CYStatement *code_;
+
+ CYWhile(CYExpression *test, CYStatement *code) :
+ test_(test),
+ code_(code)
+ {
+ }
+};
+
+struct CYLambda :
+ CYExpression
+{
+ CYIdentifier *name_;
+ CYParameter *parameters_;
+ CYSource *body_;
+
+ CYLambda(CYIdentifier *name, CYParameter *parameters, CYSource *body) :
+ name_(name),
+ parameters_(parameters),
+ body_(body)
+ {
+ }
+};
+
+struct CYFunction :
+ CYLambda
+{
+ CYFunction(CYIdentifier *name, CYParameter *parameters, CYSource *body) :
+ CYLambda(name, parameters, body)
+ {
+ }
+};
+
+struct CYContinue :
+ CYStatement
+{
+ CYIdentifier *label_;
+
+ CYContinue(CYIdentifier *label) :
+ label_(label)
+ {
+ }
+};
+
+struct CYBreak :
+ CYStatement
+{
+ CYIdentifier *label_;
+
+ CYBreak(CYIdentifier *label) :
+ label_(label)
+ {
+ }
+};
+
+struct CYReturn :
+ CYStatement
+{
+ CYExpression *value_;
+
+ CYReturn(CYExpression *value) :
+ value_(value)
+ {
+ }
+};
+
+struct CYEmpty :
+ CYStatement
+{
+};
+
+struct CYTry :
+ CYStatement
+{
+ CYStatement *try_;
+ CYCatch *catch_;
+ CYStatement *finally_;
+
+ CYTry(CYStatement *_try, CYCatch *_catch, CYStatement *finally) :
+ try_(_try),
+ catch_(_catch),
+ finally_(finally)
+ {
+ }
+};
+
+struct CYThrow :
+ CYStatement
+{
+ CYExpression *value_;
+
+ CYThrow(CYExpression *value) :
+ value_(value)
+ {
+ }
+};
+
+struct CYWith :
+ CYStatement
+{
+ CYExpression *scope_;
+ CYStatement *code_;
+
+ CYWith(CYExpression *scope, CYStatement *code) :
+ scope_(scope),
+ code_(code)
+ {
+ }
+};
+
+struct CYSwitch :
+ CYStatement
+{
+ CYExpression *value_;
+ CYClause *clauses_;
+
+ CYSwitch(CYExpression *value, CYClause *clauses) :
+ value_(value),
+ clauses_(clauses)
+ {
+ }
+};
+
+struct CYCondition :
+ CYExpression
+{
+ CYExpression *test_;
+ CYExpression *true_;
+ CYExpression *false_;
+
+ CYCondition(CYExpression *test, CYExpression *_true, CYExpression *_false) :
+ true_(_true),
+ false_(_false)
+ {
+ }
+};
+
+#define CYPostfix_(op, name) \
+ struct CY ## name : \
+ CYPostfix \
+ { \
+ CY ## name(CYExpression *lhs) : \
+ CYPostfix(lhs) \
+ { \
+ } \
+ };
+
+#define CYPrefix_(op, name) \
+ struct CY ## name : \
+ CYPrefix \
+ { \
+ CY ## name(CYExpression *rhs) : \
+ CYPrefix(rhs) \
+ { \
+ } \
+ };
+
+#define CYInfix_(op, name) \
+ struct CY ## name : \
+ CYInfix \
+ { \
+ CY ## name(CYExpression *lhs, CYExpression *rhs) : \
+ CYInfix(lhs, rhs) \
+ { \
+ } \
+ };
+
+#define CYAssignment_(op, name) \
+ struct CY ## name ## Assign : \
+ CYAssignment \
+ { \
+ CY ## name ## Assign(CYExpression *lhs, CYExpression *rhs) : \
+ CYAssignment(lhs, rhs) \
+ { \
+ } \
+ };
+
+CYPostfix_("++", PostIncrement)
+CYPostfix_("--", PostDecrement)
+
+CYPrefix_("delete", Delete)
+CYPrefix_("void", Void)
+CYPrefix_("typeof", TypeOf)
+CYPrefix_("++", PreIncrement)
+CYPrefix_("--", PreDecrement)
+CYPrefix_("-", Negate)
+CYPrefix_("~", BitwiseNot)
+CYPrefix_("!", LogicalNot)
+CYPrefix_("*", Indirect)
+CYPrefix_("&", AddressOf)
+
+CYInfix_("*", Multiply)
+CYInfix_("/", Divide)
+CYInfix_("%", Modulus)
+CYInfix_("+", Add)
+CYInfix_("-", Subtract)
+CYInfix_("<<", ShiftLeft)
+CYInfix_(">>", ShiftRightSigned)
+CYInfix_(">>>", ShiftRightUnsigned)
+CYInfix_("<", Less)
+CYInfix_(">", Greater)
+CYInfix_("<=", LessOrEqual)
+CYInfix_(">=", GreaterOrEqual)
+CYInfix_("instanceof", InstanceOf)
+CYInfix_("in", In)
+CYInfix_("==", Equal)
+CYInfix_("!=", NotEqual)
+CYInfix_("===", Identical)
+CYInfix_("!==", NotIdentical)
+CYInfix_("&", BitwiseAnd)
+CYInfix_("^", BitwiseXOr)
+CYInfix_("|", BitwiseOr)
+CYInfix_("&&", LogicalAnd)
+CYInfix_("||", LogicalOr)
+
+CYAssignment_("=", )
+CYAssignment_("*=", Multiply)
+CYAssignment_("/=", Divide)
+CYAssignment_("%=", Modulus)
+CYAssignment_("+=", Add)
+CYAssignment_("-=", Subtract)
+CYAssignment_("<<=", ShiftLeft)
+CYAssignment_(">>=", ShiftRightSigned)
+CYAssignment_(">>>=", ShiftRightUnsigned)
+CYAssignment_("&=", BitwiseAnd)
+CYAssignment_("^=", BitwiseXOr)
+CYAssignment_("|=", BitwiseOr)
+
#endif/*CYPARSER_HPP*/