From 89ab43eba54c99b17fd9ed8299953e2480c0bbf0 Mon Sep 17 00:00:00 2001 From: Hackerpilot Date: Sat, 20 Apr 2013 01:20:13 -0700 Subject: [PATCH 1/9] Initial commit --- README.md | 4 ++++ 1 file changed, 4 insertions(+) create mode 100644 README.md diff --git a/README.md b/README.md new file mode 100644 index 0000000..bdb2882 --- /dev/null +++ b/README.md @@ -0,0 +1,4 @@ +DGrammar +======== + +An attempt to completely and correctly document the grammar of the D programming language \ No newline at end of file From 6694a4a8755710c2965a805af442ec427cde4109 Mon Sep 17 00:00:00 2001 From: Hackerpilot Date: Sat, 20 Apr 2013 01:21:32 +0000 Subject: [PATCH 2/9] First version --- D.g4 | 1018 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 1018 insertions(+) create mode 100644 D.g4 diff --git a/D.g4 b/D.g4 new file mode 100644 index 0000000..ae76ff3 --- /dev/null +++ b/D.g4 @@ -0,0 +1,1018 @@ +grammar D; + +Whitespace: [\u0020\u0009\u000b\u000c\u000a\u000d]+ -> skip; +fragment EndOfLine : '\u000d' | '\u000a' | '\u000d' '\u000a' | '\u2028' | '\u2029'; + +fragment Character: [\u0001-\uffff]; +fragment WysiwygCharacter: Character | Whitespace; +fragment HexDigit: [a-fA-F0-9]; +fragment OctalDigit: [0-7]; +fragment BinDigit: [01]; +fragment DecimalDigit: [0-9]; + +fragment BlockComment: '/*' (Character | Whitespace)* '*/'; +fragment LineComment: '//' (~[\r\n])* EndOfLine; +fragment NestingBlockComment: '/+' (NestingBlockComment | Character*) '+/'; +Comment : (BlockComment | LineComment | NestingBlockComment) -> skip; + +Identifier : ([a-zA-Z_])([a-zA-Z0-9_])*; + +fragment WysiwygString : 'r"' '"' StringPostfix?; +fragment AlternativeWysiwygString : '`' WysiwygCharacter* '`' StringPostfix?; +fragment EscapeSequence : '\\\'' + | '\\"' + | '\\\\' + | '\\0' + | '\\a' + | '\\b' + | '\\f' + | '\\n' + | '\\r' + | '\\t' + | '\\v' + | '\\x' HexDigit HexDigit + | '\\' OctalDigit OctalDigit + | '\\' OctalDigit OctalDigit OctalDigit + | '\\u' HexDigit HexDigit HexDigit HexDigit + | '\\U' HexDigit HexDigit HexDigit HexDigit HexDigit HexDigit HexDigit HexDigit + | '\\&' Character+ ';'; +fragment HexStringChar : [0-9a-fA-F] | Whitespace | EndOfLine; +fragment StringPostfix : [dwc]; +fragment DoubleQuotedCharacter : EscapeSequence | ~('"' | '\''); +fragment DoubleQuotedString : '"' DoubleQuotedCharacter* '"' StringPostfix?; +fragment HexString: 'x"' HexStringChar* '"' StringPostfix?; +// fragment DelimitedString: 'q"' Delimiter WysiwygCharacter+ MatchingDelimiter '"'; +// fragment TokenString: 'q{' Token* '}'; +StringLiteral : WysiwygString | AlternativeWysiwygString | DoubleQuotedString | HexString /*| DelimitedString | TokenString*/; + +CharacterLiteral: '\'' (Character | EscapeSequence) '\''; + +IntegerLiteral: Integer IntegerSuffix?; +fragment Integer: BinaryInteger | DecimalInteger | HexadecimalInteger; +fragment IntegerSuffix: ('L' | 'u' | 'U' | 'Lu' | 'LU' | 'uL' | 'UL'); +fragment DecimalInteger: DecimalDigit (DecimalDigit | '_')*; +fragment BinaryInteger: ('0b' | '0B') BinDigit (BinDigit | '_')*; +fragment HexadecimalInteger: ('0x' | '0X') HexDigit (HexDigit | '_')*; + +FloatLiteral: (Float FloatSuffix?) | (Integer (FloatSuffix | RealSuffix)? ImaginarySuffix); +fragment Float: DecimalFloat | HexFloat; +fragment DecimalFloat: (DecimalInteger '.' DecimalDigit*); +fragment DecimalExponent: ('e' | 'E' | 'e+' | 'E+' | 'e-' | 'E-') DecimalInteger; +fragment FloatSuffix: 'F' | 'f'; +fragment RealSuffix: 'L'; +fragment ImaginarySuffix: 'i'; +fragment HexFloat: ('0x' | '0X') ((HexDigit (HexDigit | '_')* '.' HexDigit (HexDigit | '_')*) | ('.' HexDigit (HexDigit | '_')*) | (HexDigit (HexDigit | '_')*)) HexExponent; +fragment HexExponent: ('p' | 'P' | 'p+' | 'P+' | 'p-' | 'P-') DecimalDigit (DecimalDigit | '_')*; + +SpecialTokenSequence: ('#line' IntegerLiteral ('"' Character+ '"')? EndOfLine) -> skip; + +module: moduleDeclaration? declaration* + ; + +moduleDeclaration: 'module' identifierChain ';' + ; + +importDeclaration: 'static'? 'import' importList ';' + ; + +importList: singleImport (',' importList)? + | importBindings + ; + +singleImport: (Identifier '=')? identifierChain + ; + +importBindings: singleImport ':' importbindlist + ; + +importbindlist: importBind (',' importbindlist)? + ; + +importBind: Identifier ('=' Identifier)? + ; + +declarationsAndStatements: (declaration | statement)+ + ; + +declaration: attributedDeclaration + | importDeclaration + | functionDeclaration + | functionTemplateDeclaration + | variableDeclaration + | aliasThisDeclaration + | structDeclaration + | structTemplateDeclaration + | classDeclaration + | classTemplateDeclaration + | interfaceDeclaration + | interfaceTemplateDeclaration + | unionDeclaration + | unionTemplateDeclaration + | aliasDeclaration + | mixinDeclaration + | unittest + | templateDeclaration + | staticConstructor + | staticDestructor + | sharedStaticDestructor + | sharedStaticConstructor + ; + +templateParameters: '(' templateParameterList? ')' + ; + +constraint: 'if' '(' expression ')' + ; + +aliasThisDeclaration: 'alias' Identifier 'this' ';' + ; + +structDeclaration: 'struct' Identifier (structBody | ';') + ; + +structTemplateDeclaration: 'struct' Identifier templateParameters constraint? structBody + ; + +structBody: '{' declaration* '}' + ; + +classDeclaration: 'class' Identifier (':' identifierList )? classBody + ; + +classTemplateDeclaration: 'class' Identifier templateParameters constraint? classBody + ; + +classBody: '{' (declaration | invariant)* '}' + ; + +statement: ';' + | nonemptyStatement + ; + +interfaceDeclaration: 'interface' Identifier (':' identifierList)? structBody + ; + +interfaceTemplateDeclaration: 'interface' Identifier templateParameters constraint? (':' identifierList)? structBody + ; + +unionDeclaration: 'union' Identifier (structBody | ';') + ; + +unionTemplateDeclaration: 'union' Identifier parameters constraint? structBody + ; + +nonemptyStatement: nonEmptyStatementNoCaseNoDefault + | caseStatement + | caseRangeStatement + | defaultStatement + ; + +nonEmptyStatementNoCaseNoDefault: labeledStatement + | assignStatement + | ifStatement + | whileStatement + | doStatement + | forStatement + | foreachStatement + | switchStatement + | finalSwitchStatement + | continueStatement + | breakStatement + | returnStatement + | gotoStatement + | withStatement + | synchronizedStatement + | tryStatement + | throwStatement + | scopeGuardStatement + | asmStatement + | pragmaStatement + | foreachRangeStatement + | conditionalStatement + | staticAssert + | templateMixinStatement + | versionSpecification + | debugSpecification + | functionCallStatement + | deleteStatement + ; + +labeledStatement: Identifier ':' statement + ; + +returnStatement: 'return' expression? ';' + ; + +switchStatement: 'switch' '(' expression ')' blockStatement + ; + +finalSwitchStatement: 'final' switchStatement + ; + +caseStatement: 'case' argumentList ':' statementListNoCaseNoDefault + ; + +caseRangeStatement: 'case' assignExpression ':' '...' 'case' assignExpression ':' statementListNoCaseNoDefault + ; + +defaultStatement: 'default' ':' statementListNoCaseNoDefault + ; + +statementListNoCaseNoDefault: statementNoCaseNoDefault statementListNoCaseNoDefault? + ; + +statementNoCaseNoDefault: ';' + | nonEmptyStatementNoCaseNoDefault + ; + +continueStatement: 'continue' Identifier? ';' + ; + +breakStatement: 'break' Identifier? ';' + ; + +gotoStatement: 'goto' Identifier ';' + ; + +withStatement: 'with' '(' (expression | symbol | templateInstance) ')' nonEmptyStatementNoCaseNoDefault + ; + +synchronizedStatement: 'synchronized' nonEmptyStatementNoCaseNoDefault + | 'synchronized' '(' expression ')' nonEmptyStatementNoCaseNoDefault + ; + +tryStatement: 'try' nonEmptyStatementNoCaseNoDefault (catches | catches finally_ | finally_) + ; + +catches: lastcatch + | catch_ catches? + ; + +lastcatch: 'catch' nonEmptyStatementNoCaseNoDefault + ; + +catch_: 'catch' '(' type Identifier ')' nonEmptyStatementNoCaseNoDefault + ; + +finally_: 'finally' nonEmptyStatementNoCaseNoDefault + ; + +throwStatement: 'throw' expression ';' + ; + +scopeGuardStatement: 'scope' '(' Identifier ')' nonEmptyStatementNoCaseNoDefault + ; + +asmStatement: 'asm' '{' asminstructions '}' + ; + +asminstructions: asminstruction asminstructions? + ; + +asminstruction: Identifier + | 'align' IntegerLiteral + | 'align' Identifier + | Identifier ':' asminstruction + | Identifier operands + | opcode operands + ; + +operands: operand operands? + ; + +register: Identifier + | Identifier '(' IntegerLiteral ')' + ; + +opcode: Identifier + ; + +operand: asmexp + ; + +asmexp: asmlogorexp + | asmlogorexp '?' asmexp ':' asmexp + ; + +asmlogorexp: asmlogandexp + | asmlogandexp '||' asmlogandexp + ; + +asmlogandexp: asmorexp + | asmorexp '&&' asmorexp + ; + +asmorexp: asmxorexp + | asmxorexp '|' asmxorexp + ; + +asmxorexp: asmandexp + | asmandexp '^' asmandexp + ; + +asmandexp: asmequalexp + | asmequalexp '&' asmequalexp + ; + +asmequalexp: asmrelexp + | asmrelexp '==' asmrelexp + | asmrelexp '!=' asmrelexp + ; + +asmrelexp: asmshiftexp + | asmshiftexp '<' asmshiftexp + | asmshiftexp '<=' asmshiftexp + | asmshiftexp '>' asmshiftexp + | asmshiftexp '>=' asmshiftexp + ; + +asmshiftexp: asmaddexp + | asmaddexp '<<' asmaddexp + | asmaddexp '>>' asmaddexp + | asmaddexp '>>>' asmaddexp + ; + +asmaddexp: asmmulexp + | asmmulexp '+' asmmulexp + | asmmulexp '-' asmmulexp + ; + +asmmulexp: asmbrexp + | asmbrexp '*' asmbrexp + | asmbrexp '/' asmbrexp + | asmbrexp '%' asmbrexp + ; + +asmbrexp: asmunaexp + | asmbrexp '[' asmexp ']' + ; + +asmunaexp: asmtypeprefix asmexp + | Identifier asmexp + | '+' asmunaexp + | '-' asmunaexp + | '!' asmunaexp + | '~' asmunaexp + | asmprimaryexp + ; + +asmprimaryexp: IntegerLiteral + | FloatLiteral + | '$' + | register + | identifierChain + ; + +asmtypeprefix: Identifier Identifier + | 'byte' Identifier + | 'short' Identifier + | 'int' Identifier + | 'float' Identifier + | 'double' Identifier + | 'real' Identifier + ; + +pragmaStatement: pragma ';' + ; + +pragma: 'pragma' '(' Identifier (',' argumentList)? ')' + ; + +foreachRangeStatement: 'foreach' '(' foreachType ';' expression '..' expression ')' nonEmptyStatementNoCaseNoDefault + ; + +conditionalStatement: compileCondition nonEmptyStatementNoCaseNoDefault + | compileCondition nonEmptyStatementNoCaseNoDefault 'else' nonEmptyStatementNoCaseNoDefault + ; + +compileCondition: versionCondition + | debugCondition + | staticIfCondition + ; + +versionCondition: 'version' '(' IntegerLiteral ')' + | 'version' '(' Identifier ')' + | 'version' '(' 'unittest' ')' + | 'version' '(' 'assert' ')' + ; + +versionSpecification: 'version' '=' Identifier ';' + | 'version' '=' IntegerLiteral ';' + ; + +castExpression: 'cast' '(' type ')' unaryExpression + | 'cast' '(' castQualifier ')' unaryExpression + | 'cast' '(' ')' unaryExpression + ; + +castQualifier: 'const' + | 'const' 'shared' + | 'shared' 'const' + | 'inout' + | 'inout' 'shared' + | 'shared' 'inout' + | 'immutable' + | 'shared' + ; + +debugCondition: 'debug' + | 'debug' '(' IntegerLiteral ')' + | 'debug' '(' Identifier ')' + ; + +debugSpecification: 'debug' '=' Identifier ';' + | 'debug' '=' IntegerLiteral ';' + ; + +staticIfCondition: 'static' 'if' '(' assignExpression ')' + ; + +staticAssert: 'static' 'assert' '(' assignExpression (',' assignExpression)? ')' ';' + ; + +templateMixinStatement: 'mixin' mixinTemplateName (templateArguments | Identifier | templateArguments Identifier) ';' + ; + +mixinTemplateName: '.' qualifiedIdentifierChain + | qualifiedIdentifierChain + | typeof '.' qualifiedIdentifierChain + ; + +qualifiedIdentifierChain: Identifier + | Identifier '.' qualifiedIdentifierChain + | templateInstance '.' qualifiedIdentifierChain + ; + +functionCallStatement: functionCallExpression ';' + ; + +deleteStatement: deleteExpression ';' + ; + +assignStatement: unaryExpression assignOperator assignExpression ';' + | preIncDecExpression ';' + | postIncDecExpression ';' + ; + +ifStatement: 'if' '(' expression ')' statement ('else' statement)? + ; + +forStatement: 'for' '(' initialize expression ';' expression ')' statement + | 'for' '(' initialize ';' expression ')' statement + ; + +initialize: ';' + | nonemptyStatement + ; + +foreachStatement: ('foreach' | 'foreach_reverse') '(' foreachTypeList ';' expression ')' nonEmptyStatementNoCaseNoDefault + ; + +foreachTypeList: foreachType + | foreachType ',' foreachTypeList + ; + +foreachType: 'ref'? type? Identifier + ; + +expression: assignExpression + | assignExpression ',' expression + ; + +identifierOrTemplateInstance: Identifier + | templateInstance + ; + +templateInstance: Identifier '!' (Identifier | '(' identifierList? ')') + ; + +unaryExpression: '&' unaryExpression + | '!' unaryExpression + | '*' unaryExpression + | '+' unaryExpression + | '-' unaryExpression + | '~' unaryExpression + | preIncDecExpression + | newExpression + | deleteExpression + | castExpression + | primaryExpression + /*| postIncDecExpression*/ + | unaryExpression ('++'| '--') + | unaryExpression '[' ']' + | unaryExpression '[' argumentList ']' + | unaryExpression '[' assignExpression '..' assignExpression ']' + | unaryExpression '.' identifierOrTemplateInstance + ; + +powExpression: unaryExpression + | unaryExpression '^^' powExpression + ; + +postIncDecExpression: unaryExpression ('++' | '--') + ; + +preIncDecExpression: ('++' | '--') unaryExpression + ; + +primaryExpression: identifierOrTemplateInstance + | '.' identifierOrTemplateInstance + | type '.' Identifier + | typeofExpression + | typeidExpression + | 'this' + | 'super' + | 'null' + | 'true' + | 'false' + | '__file__' + | '__module__' + | '__line__' + | '__FUNCTION__' + | '__PRETTY_FUNCTION__' + | IntegerLiteral + | FloatLiteral + | StringLiteral + | CharacterLiteral + | arrayLiteral + | assocArrayLiteral + | '(' expression ')' + | isExpression + | lambdaExpression + | traitsExpression + ; + +typeofExpression: 'typeof' '(' (expression | 'return') ')' + ; + +typeidExpression: 'typeid' '(' type ')' + | 'typeid' '(' expression ')' + ; + +isExpression: 'is' '(' type Identifier? (((':' | '==') typeSpecialization (',' templateParameterList)? ))? ')' + ; + +templateParameterList: templateParameter (','? templateParameter)* + ; + +templateParameter: templateTypeParameter + | templateValueParameter + | templateAliasParameter + | templateTupleParameter + | templateThisParameter + ; + +templateTypeParameter: Identifier templateTypeParameterSpecialization? templateTypeParameterDefault? + ; + +templateTypeParameterSpecialization: ':' type + ; + +templateTypeParameterDefault: '=' type + ; + +templateValueParameter: type Identifier templateValueParameterSpecialization? templateValueParameterDefault? + ; + +templateValueParameterSpecialization: ':' expression + ; + +templateValueParameterDefault: '=' ('__file__' | '__module__' | '__line__' | '__FUNCTION__' | '__PRETTY_FUNCTION__' | assignExpression) + ; + +templateAliasParameter: 'alias' type? Identifier templatealiasparameterspecialization? templatealiasparameterdefault? + ; + +templatealiasparameterspecialization: ':' (type | expression) + ; + +templatealiasparameterdefault: '=' (type | expression) + ; + +templateTupleParameter: Identifier '...' + ; + +templateThisParameter: 'this' templateTypeParameter + ; + +typeSpecialization: type + | 'struct' + | 'union' + | 'class' + | 'interface' + | 'enum' + | 'function' + | 'delegate' + | 'super' + | 'const' + | 'immutable' + | 'inout' + | 'shared' + | 'return' + | '__parameters' + ; + +templateArguments: '!' ('(' templateArgumentList? ')' | templateSingleArgument) + ; + +templateArgumentList: templateArgument (',' templateArgument?)* + ; + +templateArgument: type + | assignExpression + | symbol + ; + +symbol: '.'? symbolTail + ; + +symbolTail: identifierOrTemplateInstance ('.' symbolTail)? + ; + +templateSingleArgument: Identifier + | builtinType + | CharacterLiteral + | StringLiteral + | IntegerLiteral + | FloatLiteral + | 'true' + | 'false' + | 'null' + | 'this' + | '__FILE__' + | '__MODULE__' + | '__LINE__' + | '__FUNCTION__' + | '__PRETTY_FUNCTION__' + ; + +functionCallExpression: unaryExpression arguments + ; + +arguments: '(' argumentList? ')' + ; + +argumentList: assignExpression (',' argumentList?)? + ; + +newExpression: 'new' type ('[' assignExpression ']' | arguments | ) + | newAnonClassExpression + ; + +newAnonClassExpression: 'new' arguments? 'class' arguments? Identifier identifierList? classBody + ; + +deleteExpression: 'delete' unaryExpression + ; + +ternaryexpression: orOrExpression '?' expression ':' conditionalExpression + ; + +assignExpression: conditionalExpression + | conditionalExpression assignOperator assignExpression + ; + +conditionalExpression: orOrExpression + | ternaryexpression + ; + +orOrExpression: andAndExpression + | orOrExpression '||' andAndExpression + ; + +andAndExpression: orExpression + | cmpExpression + | andAndExpression '&&' (orExpression | cmpExpression) + ; + +orExpression: xorExpression + | orExpression '|' xorExpression + ; + +xorExpression: andExpression + | xorExpression '^' andExpression + ; + +andExpression: shiftExpression + | andExpression '&' shiftExpression + ; + +cmpExpression: shiftExpression + | equalExpression + | identityExpression + | relExpression + | inExpression + ; + +equalExpression: shiftExpression ('==' | '!=') shiftExpression; + +identityExpression: shiftExpression ('is' | '!is') shiftExpression; + +relExpression: shiftExpression relOperator shiftExpression; + +inExpression: shiftExpression ('in' | '!in') shiftExpression; + +shiftExpression: addExpression + | shiftExpression ('<<' | '>>' | '>>>') addExpression; + +addExpression: mulExpression + | addExpression ('+' | '-' | '~') mulExpression + ; + +mulExpression: unaryExpression + | mulExpression ('*' | '/' | '%') unaryExpression; + +assignOperator: '=' + | '>>>=' + | '>>=' + | '<<=' + | '+=' + | '-=' + | '*=' + | '%=' + | '&=' + | '/=' + | '|=' + | '^^=' + | '^=' + | '~=' + ; + +relOperator: '<' + | '<=' + | '>' + | '>=' + | '!<>=' + | '!<>' + | '<>' + | '<>=' + | '!>' + | '!>=' + | '!<' + | '!<=' + ; + +whileStatement: 'while' '(' expression ')' blockStatement + ; + +doStatement: 'do' blockStatement 'while' '(' expression ')' ';' + ; + +blockStatement: '{' declarationsAndStatements? '}' + ; + +functionDeclaration: type Identifier parameters (functionBody | ';') + ; + +functionTemplateDeclaration: type Identifier templateParameters parameters constraint? functionBody + ; + +type: typeConstructors? type2 + ; + +type2: type3 typesuffix? + | type2 typesuffix + ; + +type3: builtinType + | '.' identifierChain + | identifierChain + | typeof + | typeof '.' identifierChain + | 'const' '(' type ')' + | 'immutable' '(' type ')' + | 'shared' '(' type ')' + | 'inout' '(' type ')' + | 'delegate' parameters memberFunctionAttributes? + | 'function' parameters memberFunctionAttributes? + ; + +typesuffix: '*' + | '[' ']' + | '[' type ']' + | '[' assignExpression ']' + ; + +builtinType: 'bool' + | 'byte' + | 'ubyte' + | 'short' + | 'ushort' + | 'int' + | 'uint' + | 'long' + | 'ulong' + | 'char' + | 'wchar' + | 'dchar' + | 'float' + | 'double' + | 'real' + | 'ifloat' + | 'idouble' + | 'ireal' + | 'cfloat' + | 'cdouble' + | 'creal' + | 'void' + ; + +typeConstructors: typeConstructor typeConstructors? + ; + +typeConstructor: 'const' + | 'immutable' + | 'inout' + | 'shared' + ; + +typeof: 'typeof' '(' (expression | 'return') ')' + ; + +parameters: '(' (parameter (',' parameter)*)? ')' + ; + +parameter: parameterAttribute? type ('...' | (Identifier ('=' defaultInitializerExpression)?))? + ; + +defaultInitializerExpression: assignExpression + | '__file__' + | '__module__' + | '__line__' + | '__FUNCTION__' + | '__PRETTY_FUNCTION__' + ; + +parameterAttribute: 'auto' + | 'final' + | 'in' + | 'lazy' + | 'out' + | 'ref' + | 'scope' + | typeConstructor + ; + +functionAttribute: 'nothrow' + | 'pure' + | atAttribute + ; + +memberFunctionAttribute: 'const' + | 'immutable' + | 'inout' + | 'shared' + | functionAttribute + ; + +memberFunctionAttributes: memberFunctionAttribute+ + ; + +functionBody: blockStatement + | (inStatement | outStatement | outStatement inStatement | inStatement outStatement)? bodyStatement + ; + +inStatement: 'in' blockStatement + ; + +outStatement: 'out' ('(' Identifier ')')? blockStatement + ; + +bodyStatement: 'body' blockStatement + ; + +aliasDeclaration: 'alias' (aliasinitializer (',' aliasinitializer)* | type declarator) ';' + ; + +aliasinitializer: Identifier '=' type + ; + +variableDeclaration: type declarator (',' declarator)* ';' + ; + +declarator: Identifier ('=' initializer)? + ; + +mixinDeclaration: 'mixin' '(' assignExpression ')' ';' + ; + +identifierList: Identifier (',' Identifier)* + ; + +identifierChain: Identifier ('.' Identifier)* + ; + +attributedDeclaration: attribute (':' | declaration | '{' declaration* '}') + ; + +attribute: linkageattribute + | alignattribute + | pragma + | protectionAttribute + | 'deprecated' + | 'extern' + | 'final' + | 'synchronized' + | 'override' + | 'abstract' + | 'const' + | 'auto' + | 'scope' + | '__gshared' + | 'shared' + | 'immutable' + | 'inout' + | atAttribute + ; + +linkageattribute: 'extern' '(' Identifier '++'? ')' + ; + +atAttribute: '@' (Identifier | '(' argumentList ')' | functionCallExpression) + ; + +alignattribute: 'align' ('(' IntegerLiteral ')')? + ; + +protectionAttribute: 'private' + | 'package' + | 'protected' + | 'public' + | 'export' + ; + +traitsExpression: 'traits' '(' Identifier ',' traitsArgument (',' traitsArgument)* ')' + ; + +traitsArgument: assignExpression + | type + ; + +unittest: 'unittest' blockStatement + ; + +templateDeclaration: 'template' Identifier templateParameters constraint? '{' declaration+ '}' + ; + +staticConstructor: 'static' 'this' '(' ')' functionBody + ; + +staticDestructor: 'static' '~' 'this' '(' ')' functionBody + ; + +sharedStaticDestructor: 'shared' 'static' 'this' '(' ')' functionBody + ; + +sharedStaticConstructor: 'shared' 'static' '~' 'this' '(' ')' functionBody + ; + +invariant: 'invariant' '(' ')' blockStatement + ; + +arrayinitializer: '[' arraymemberinitializations? ']' + ; + +arraymemberinitializations: arraymemberinitialization + | arraymemberinitialization ',' + | arraymemberinitialization ',' arraymemberinitializations + ; + +arraymemberinitialization: (assignExpression ':')? nonVoidInitializer + ; + +initializer: voidinitializer + | nonVoidInitializer + ; + +voidinitializer: 'void' + ; + +nonVoidInitializer: assignExpression + | arrayinitializer + | structinitializer + ; + +structinitializer: '{' structMemberInitializers? '}' + ; + +structMemberInitializers: structMemberInitializer (','? structMemberInitializers)? + ; + +structMemberInitializer: (Identifier ':')? nonVoidInitializer + ; + +lambdaExpression: (Identifier | parameters functionAttribute? ) '=>' assignExpression + ; + +arrayLiteral: '[' argumentList ']' + ; + +assocArrayLiteral: '[' keyValuePairs ']' + ; + +keyValuePairs: keyValuePair + | keyValuePair ',' keyValuePairs + ; + +keyValuePair: assignExpression ':' assignExpression + ; From adf8f09c7d17bdcd908b12a58d2433c1d952bbec Mon Sep 17 00:00:00 2001 From: Hackerpilot Date: Sat, 20 Apr 2013 23:22:14 -0700 Subject: [PATCH 3/9] Fixed accidental lower-casing of constants --- D.g4 | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/D.g4 b/D.g4 index ae76ff3..c0b44a8 100644 --- a/D.g4 +++ b/D.g4 @@ -525,9 +525,9 @@ primaryExpression: identifierOrTemplateInstance | 'null' | 'true' | 'false' - | '__file__' - | '__module__' - | '__line__' + | '__FILE__' + | '__MODULE__' + | '__LINE__' | '__FUNCTION__' | '__PRETTY_FUNCTION__' | IntegerLiteral @@ -577,7 +577,7 @@ templateValueParameter: type Identifier templateValueParameterSpecialization? te templateValueParameterSpecialization: ':' expression ; -templateValueParameterDefault: '=' ('__file__' | '__module__' | '__line__' | '__FUNCTION__' | '__PRETTY_FUNCTION__' | assignExpression) +templateValueParameterDefault: '=' ('__FILE__' | '__MODULE__' | '__LINE__' | '__FUNCTION__' | '__PRETTY_FUNCTION__' | assignExpression) ; templateAliasParameter: 'alias' type? Identifier templatealiasparameterspecialization? templatealiasparameterdefault? @@ -836,9 +836,9 @@ parameter: parameterAttribute? type ('...' | (Identifier ('=' defaultInitializer ; defaultInitializerExpression: assignExpression - | '__file__' - | '__module__' - | '__line__' + | '__FILE__' + | '__MODULE__' + | '__LINE__' | '__FUNCTION__' | '__PRETTY_FUNCTION__' ; From 63a254b9cbca90d9eb3bf2a7786b3c3171d392c7 Mon Sep 17 00:00:00 2001 From: Hackerpilot Date: Sun, 21 Apr 2013 14:09:52 -0700 Subject: [PATCH 4/9] Cleanup --- D.g4 | 78 +++++++++++++++++++++++++++++------------------------------- 1 file changed, 38 insertions(+), 40 deletions(-) diff --git a/D.g4 b/D.g4 index c0b44a8..20741fb 100644 --- a/D.g4 +++ b/D.g4 @@ -430,7 +430,7 @@ staticIfCondition: 'static' 'if' '(' assignExpression ')' staticAssert: 'static' 'assert' '(' assignExpression (',' assignExpression)? ')' ';' ; -templateMixinStatement: 'mixin' mixinTemplateName (templateArguments | Identifier | templateArguments Identifier) ';' +templateMixinStatement: 'mixin' mixinTemplateName templateArguments? Identifier? ';' ; mixinTemplateName: '.' qualifiedIdentifierChain @@ -454,6 +454,22 @@ assignStatement: unaryExpression assignOperator assignExpression ';' | postIncDecExpression ';' ; +assignOperator: '=' + | '>>>=' + | '>>=' + | '<<=' + | '+=' + | '-=' + | '*=' + | '%=' + | '&=' + | '/=' + | '|=' + | '^^=' + | '^=' + | '~=' + ; + ifStatement: 'if' '(' expression ')' statement ('else' statement)? ; @@ -655,7 +671,7 @@ arguments: '(' argumentList? ')' argumentList: assignExpression (',' argumentList?)? ; -newExpression: 'new' type ('[' assignExpression ']' | arguments | ) +newExpression: 'new' type ('[' assignExpression ']' | arguments)? | newAnonClassExpression ; @@ -665,15 +681,12 @@ newAnonClassExpression: 'new' arguments? 'class' arguments? Identifier identifie deleteExpression: 'delete' unaryExpression ; -ternaryexpression: orOrExpression '?' expression ':' conditionalExpression +assignExpression: ternaryExpression + | ternaryExpression assignOperator assignExpression ; -assignExpression: conditionalExpression - | conditionalExpression assignOperator assignExpression - ; - -conditionalExpression: orOrExpression - | ternaryexpression +ternaryExpression: orOrExpression + | orOrExpression '?' expression ':' ternaryExpression ; orOrExpression: andAndExpression @@ -710,34 +723,6 @@ identityExpression: shiftExpression ('is' | '!is') shiftExpression; relExpression: shiftExpression relOperator shiftExpression; -inExpression: shiftExpression ('in' | '!in') shiftExpression; - -shiftExpression: addExpression - | shiftExpression ('<<' | '>>' | '>>>') addExpression; - -addExpression: mulExpression - | addExpression ('+' | '-' | '~') mulExpression - ; - -mulExpression: unaryExpression - | mulExpression ('*' | '/' | '%') unaryExpression; - -assignOperator: '=' - | '>>>=' - | '>>=' - | '<<=' - | '+=' - | '-=' - | '*=' - | '%=' - | '&=' - | '/=' - | '|=' - | '^^=' - | '^=' - | '~=' - ; - relOperator: '<' | '<=' | '>' @@ -752,6 +737,19 @@ relOperator: '<' | '!<=' ; +inExpression: shiftExpression ('in' | '!in') shiftExpression; + +shiftExpression: addExpression + | shiftExpression ('<<' | '>>' | '>>>') addExpression; + +addExpression: mulExpression + | addExpression ('+' | '-' | '~') mulExpression + ; + +mulExpression: unaryExpression + | mulExpression ('*' | '/' | '%') unaryExpression + ; + whileStatement: 'while' '(' expression ')' blockStatement ; @@ -770,8 +768,8 @@ functionTemplateDeclaration: type Identifier templateParameters parameters const type: typeConstructors? type2 ; -type2: type3 typesuffix? - | type2 typesuffix +type2: type3 typeSuffix? + | type2 typeSuffix ; type3: builtinType @@ -787,7 +785,7 @@ type3: builtinType | 'function' parameters memberFunctionAttributes? ; -typesuffix: '*' +typeSuffix: '*' | '[' ']' | '[' type ']' | '[' assignExpression ']' From 461893dee3b93d69dd6a557ec45afa0918fda133 Mon Sep 17 00:00:00 2001 From: Hackerpilot Date: Mon, 22 Apr 2013 00:59:10 -0700 Subject: [PATCH 5/9] Added token rules. Fixed a few errors. --- D.g4 | 447 +++++++++++++++++++++++++++++++++++++++-------------------- 1 file changed, 293 insertions(+), 154 deletions(-) diff --git a/D.g4 b/D.g4 index 20741fb..5fa5aaa 100644 --- a/D.g4 +++ b/D.g4 @@ -1,5 +1,187 @@ grammar D; +Assign: '='; +At: '@'; +BitAnd: '&'; +BitAndEqual: '&='; +BitOr: '|'; +BitOrEqual: '|='; +CatEqual: '~='; +Colon: ':'; +Comma: ','; +Decrement: '--'; +Div: '/'; +DivEqual: '/='; +Dollar: '$'; +Dot: '.'; +Equal: '=='; +GoesTo: '=>'; +Greater: '>'; +GreaterEqual: '>='; +Hash: '#'; +Increment: '++'; +LBrace: '{'; +LBracket: '['; +Less: '<'; +LessEqual: '<='; +LessEqualGreater: '<>='; +LessOrGreater: '<>'; +LogicAnd: '&&'; +LogicOr: '||'; +LParen: '('; +Minus: '-'; +MinusEqual: '-='; +Mod: '%'; +ModEqual: '%='; +MulEqual: '*='; +Not: '!'; +NotEqual: '!='; +NotGreater: '!>'; +NotGreaterEqual: '!>='; +NotLess: '!<'; +NotLessEqual: '!<='; +NotLessEqualGreater: '!<>'; +Plus: '+'; +PlusEqual: '+='; +Pow: '^^'; +PowEqual: '^^='; +RBrace: '}'; +RBracket: ']'; +RParen: ')'; +Semicolon: ';'; +ShiftLeft: '<<'; +ShiftLeftEqual: '<<='; +ShiftRight: '>>'; +ShiftRightEqual: '>>='; +Slice: '..'; +Star: '*'; +Ternary: '?'; +Tilde: '~'; +Unordered: '!<>='; +UnsignedShiftRight: '>>>'; +UnsignedShiftRightEqual: '>>>='; +Vararg: '...'; +Xor: '^'; +XorEqual: '^='; +Bool: 'bool'; +Byte: 'byte'; +Cdouble: 'cdouble'; +Cent: 'cent'; +Cfloat: 'cfloat'; +Char: 'char'; +Creal: 'creal'; +Dchar: 'dchar'; +Double: 'double'; +Float: 'float'; +Function: 'function'; +Idouble: 'idouble'; +Ifloat: 'ifloat'; +Int: 'int'; +Ireal: 'ireal'; +Long: 'long'; +Real: 'real'; +Short: 'short'; +Ubyte: 'ubyte'; +Ucent: 'ucent'; +Uint: 'uint'; +Ulong: 'ulong'; +Ushort: 'ushort'; +Void: 'void'; +Wchar: 'wchar'; +Align: 'align'; +Deprecated: 'deprecated'; +Extern: 'extern'; +Pragma: 'pragma'; +Export: 'export'; +Package: 'package'; +Private: 'private'; +Protected: 'protected'; +Public: 'public'; +Abstract: 'abstract'; +Auto: 'auto'; +Const: 'const'; +Final: 'final'; +Gshared: '__gshared'; +Immutable: 'immutable'; +Inout: 'inout'; +Scope: 'scope'; +Shared: 'shared'; +Static: 'static'; +Synchronized: 'synchronized'; +Alias: 'alias'; +Asm: 'asm'; +Assert: 'assert'; +Body: 'body'; +Break: 'break'; +Case: 'case'; +Cast: 'cast'; +Catch: 'catch'; +Class: 'class'; +Continue: 'continue'; +Debug: 'debug'; +Default: 'default'; +Delegate: 'delegate'; +Delete: 'delete'; +Do: 'do'; +Else: 'else'; +Enum: 'enum'; +False: 'false'; +Finally: 'finally'; +Foreach: 'foreach'; +Foreach_reverse: 'foreach_reverse'; +For: 'for'; +Goto: 'goto'; +If: 'if'; +Import: 'import'; +In: 'in'; +Interface: 'interface'; +Invariant: 'invariant'; +Is: 'is'; +Lazy: 'lazy'; +Macro: 'macro'; +Mixin: 'mixin'; +Module: 'module'; +New: 'new'; +Nothrow: 'nothrow'; +Null: 'null'; +Out: 'out'; +Override: 'override'; +Pure: 'pure'; +Ref: 'ref'; +Return: 'return'; +Struct: 'struct'; +Super: 'super'; +Switch: 'switch'; +Template: 'template'; +This: 'this'; +Throw: 'throw'; +True: 'true'; +Try: 'try'; +Typedef: 'typedef'; +Typeid: 'typeid'; +Typeof: 'typeof'; +Union: 'union'; +Unittest: 'unittest'; +Version: 'version'; +Volatile: 'volatile'; +While: 'while'; +With: 'with'; + +SpecialDate: '__DATE__'; +SpecialEof: '__EOF__'; +SpecialTime: '__TIME__'; +Specialimestamp: '__TIMESTAMP__'; +SpecialVendor: '__VENDOR__'; +SpecialVersion: '__VERSION__'; +SpecialFile: '__FILE__'; +SpecialLine: '__LINE__'; +SpecialModule: '__MODULE__'; +SpecialFunction: '__FUNCTION__'; +SpecialPrettyFunction: '__PRETTY_FUNCTION__'; +Traits: '__traits'; +Parameters: '__parameters'; +Vector: '__vector'; + Whitespace: [\u0020\u0009\u000b\u000c\u000a\u000d]+ -> skip; fragment EndOfLine : '\u000d' | '\u000a' | '\u000d' '\u000a' | '\u2028' | '\u2029'; @@ -54,8 +236,8 @@ fragment DecimalInteger: DecimalDigit (DecimalDigit | '_')*; fragment BinaryInteger: ('0b' | '0B') BinDigit (BinDigit | '_')*; fragment HexadecimalInteger: ('0x' | '0X') HexDigit (HexDigit | '_')*; -FloatLiteral: (Float FloatSuffix?) | (Integer (FloatSuffix | RealSuffix)? ImaginarySuffix); -fragment Float: DecimalFloat | HexFloat; +FloatLiteral: (FloatOption FloatSuffix?) | (Integer (FloatSuffix | RealSuffix)? ImaginarySuffix); +fragment FloatOption: DecimalFloat | HexFloat; fragment DecimalFloat: (DecimalInteger '.' DecimalDigit*); fragment DecimalExponent: ('e' | 'E' | 'e+' | 'E+' | 'e-' | 'E-') DecimalInteger; fragment FloatSuffix: 'F' | 'f'; @@ -72,42 +254,15 @@ module: moduleDeclaration? declaration* moduleDeclaration: 'module' identifierChain ';' ; -importDeclaration: 'static'? 'import' importList ';' - ; - -importList: singleImport (',' importList)? - | importBindings - ; - -singleImport: (Identifier '=')? identifierChain - ; - -importBindings: singleImport ':' importbindlist - ; - -importbindlist: importBind (',' importbindlist)? - ; - -importBind: Identifier ('=' Identifier)? - ; - -declarationsAndStatements: (declaration | statement)+ - ; - declaration: attributedDeclaration | importDeclaration | functionDeclaration - | functionTemplateDeclaration | variableDeclaration | aliasThisDeclaration | structDeclaration - | structTemplateDeclaration | classDeclaration - | classTemplateDeclaration | interfaceDeclaration - | interfaceTemplateDeclaration | unionDeclaration - | unionTemplateDeclaration | aliasDeclaration | mixinDeclaration | unittest @@ -118,28 +273,41 @@ declaration: attributedDeclaration | sharedStaticConstructor ; +importDeclaration: 'static'? 'import' importList ';' + ; + +importList: singleImport (',' importList)? + | importBindings + ; + +singleImport: (Identifier '=')? identifierChain + ; + +importBindings: singleImport ':' importBindList + ; + +importBindList: importBind (',' importBind)? + ; + +importBind: Identifier ('=' Identifier)? + ; + +aliasThisDeclaration: 'alias' Identifier 'this' ';' + ; + +structDeclaration: 'struct' Identifier (templateParameters constraint? structBody | (structBody | ';')) + ; + templateParameters: '(' templateParameterList? ')' ; constraint: 'if' '(' expression ')' ; -aliasThisDeclaration: 'alias' Identifier 'this' ';' - ; - -structDeclaration: 'struct' Identifier (structBody | ';') - ; - -structTemplateDeclaration: 'struct' Identifier templateParameters constraint? structBody - ; - structBody: '{' declaration* '}' ; -classDeclaration: 'class' Identifier (':' identifierList )? classBody - ; - -classTemplateDeclaration: 'class' Identifier templateParameters constraint? classBody +classDeclaration: 'class' Identifier (templateParameters constraint?)? (':' identifierList )? classBody ; classBody: '{' (declaration | invariant)* '}' @@ -149,16 +317,10 @@ statement: ';' | nonemptyStatement ; -interfaceDeclaration: 'interface' Identifier (':' identifierList)? structBody +interfaceDeclaration: 'interface' Identifier (templateParameters constraint?)? (':' identifierList)? structBody ; -interfaceTemplateDeclaration: 'interface' Identifier templateParameters constraint? (':' identifierList)? structBody - ; - -unionDeclaration: 'union' Identifier (structBody | ';') - ; - -unionTemplateDeclaration: 'union' Identifier parameters constraint? structBody +unionDeclaration: 'union' Identifier ((templateParameters constraint? structBody)? | (structBody | ';')) ; nonemptyStatement: nonEmptyStatementNoCaseNoDefault @@ -484,78 +646,20 @@ initialize: ';' foreachStatement: ('foreach' | 'foreach_reverse') '(' foreachTypeList ';' expression ')' nonEmptyStatementNoCaseNoDefault ; -foreachTypeList: foreachType - | foreachType ',' foreachTypeList +foreachTypeList: foreachType (',' foreachType)* ; foreachType: 'ref'? type? Identifier ; -expression: assignExpression - | assignExpression ',' expression +expression: assignExpression (',' assignExpression)* ; identifierOrTemplateInstance: Identifier | templateInstance ; -templateInstance: Identifier '!' (Identifier | '(' identifierList? ')') - ; - -unaryExpression: '&' unaryExpression - | '!' unaryExpression - | '*' unaryExpression - | '+' unaryExpression - | '-' unaryExpression - | '~' unaryExpression - | preIncDecExpression - | newExpression - | deleteExpression - | castExpression - | primaryExpression - /*| postIncDecExpression*/ - | unaryExpression ('++'| '--') - | unaryExpression '[' ']' - | unaryExpression '[' argumentList ']' - | unaryExpression '[' assignExpression '..' assignExpression ']' - | unaryExpression '.' identifierOrTemplateInstance - ; - -powExpression: unaryExpression - | unaryExpression '^^' powExpression - ; - -postIncDecExpression: unaryExpression ('++' | '--') - ; - -preIncDecExpression: ('++' | '--') unaryExpression - ; - -primaryExpression: identifierOrTemplateInstance - | '.' identifierOrTemplateInstance - | type '.' Identifier - | typeofExpression - | typeidExpression - | 'this' - | 'super' - | 'null' - | 'true' - | 'false' - | '__FILE__' - | '__MODULE__' - | '__LINE__' - | '__FUNCTION__' - | '__PRETTY_FUNCTION__' - | IntegerLiteral - | FloatLiteral - | StringLiteral - | CharacterLiteral - | arrayLiteral - | assocArrayLiteral - | '(' expression ')' - | isExpression - | lambdaExpression - | traitsExpression +templateInstance: Identifier templateArguments ; typeofExpression: 'typeof' '(' (expression | 'return') ')' @@ -578,19 +682,10 @@ templateParameter: templateTypeParameter | templateThisParameter ; -templateTypeParameter: Identifier templateTypeParameterSpecialization? templateTypeParameterDefault? +templateTypeParameter: Identifier (':' type)? ('=' type)? ; -templateTypeParameterSpecialization: ':' type - ; - -templateTypeParameterDefault: '=' type - ; - -templateValueParameter: type Identifier templateValueParameterSpecialization? templateValueParameterDefault? - ; - -templateValueParameterSpecialization: ':' expression +templateValueParameter: type Identifier (':' expression)? templateValueParameterDefault? ; templateValueParameterDefault: '=' ('__FILE__' | '__MODULE__' | '__LINE__' | '__FUNCTION__' | '__PRETTY_FUNCTION__' | assignExpression) @@ -719,25 +814,11 @@ cmpExpression: shiftExpression equalExpression: shiftExpression ('==' | '!=') shiftExpression; -identityExpression: shiftExpression ('is' | '!is') shiftExpression; +identityExpression: shiftExpression ('is' | '!' 'is') shiftExpression; -relExpression: shiftExpression relOperator shiftExpression; +relExpression: shiftExpression ('<' | '<=' | '>' | '>=' | '!<>=' | '!<>' | '<>' | '<>=' | '!>' | '!>=' | '!<' | '!<=') shiftExpression; -relOperator: '<' - | '<=' - | '>' - | '>=' - | '!<>=' - | '!<>' - | '<>' - | '<>=' - | '!>' - | '!>=' - | '!<' - | '!<=' - ; - -inExpression: shiftExpression ('in' | '!in') shiftExpression; +inExpression: shiftExpression ('in' | '!' 'in') shiftExpression; shiftExpression: addExpression | shiftExpression ('<<' | '>>' | '>>>') addExpression; @@ -746,8 +827,63 @@ addExpression: mulExpression | addExpression ('+' | '-' | '~') mulExpression ; -mulExpression: unaryExpression - | mulExpression ('*' | '/' | '%') unaryExpression +mulExpression: powExpression + | mulExpression ('*' | '/' | '%') powExpression + ; + +powExpression: unaryExpression + | unaryExpression '^^' powExpression + ; + +unaryExpression: primaryExpression + | '&' unaryExpression + | '!' unaryExpression + | '*' unaryExpression + | '+' unaryExpression + | '-' unaryExpression + | '~' unaryExpression + | preIncDecExpression + | newExpression + | deleteExpression + | castExpression + | unaryExpression ('++'| '--') /* postIncDecExpression */ /* This causes an error in ANTLR */ + | unaryExpression '[' ']' + | unaryExpression '[' argumentList ']' + | unaryExpression '[' assignExpression '..' assignExpression ']' + | unaryExpression '.' identifierOrTemplateInstance + ; + +postIncDecExpression: unaryExpression ('++' | '--') + ; + +preIncDecExpression: ('++' | '--') unaryExpression + ; + +primaryExpression: identifierOrTemplateInstance + | '.' identifierOrTemplateInstance + | type '.' Identifier + | typeofExpression + | typeidExpression + | 'this' + | 'super' + | 'null' + | 'true' + | 'false' + | '__FILE__' + | '__MODULE__' + | '__LINE__' + | '__FUNCTION__' + | '__PRETTY_FUNCTION__' + | IntegerLiteral + | FloatLiteral + | StringLiteral + | CharacterLiteral + | arrayLiteral + | assocArrayLiteral + | '(' expression ')' + | isExpression + | lambdaExpression + | traitsExpression ; whileStatement: 'while' '(' expression ')' blockStatement @@ -759,6 +895,9 @@ doStatement: 'do' blockStatement 'while' '(' expression ')' ';' blockStatement: '{' declarationsAndStatements? '}' ; +declarationsAndStatements: (declaration | statement)+ + ; + functionDeclaration: type Identifier parameters (functionBody | ';') ; @@ -815,7 +954,7 @@ builtinType: 'bool' | 'void' ; -typeConstructors: typeConstructor typeConstructors? +typeConstructors: typeConstructor+ ; typeConstructor: 'const' @@ -830,15 +969,7 @@ typeof: 'typeof' '(' (expression | 'return') ')' parameters: '(' (parameter (',' parameter)*)? ')' ; -parameter: parameterAttribute? type ('...' | (Identifier ('=' defaultInitializerExpression)?))? - ; - -defaultInitializerExpression: assignExpression - | '__FILE__' - | '__MODULE__' - | '__LINE__' - | '__FUNCTION__' - | '__PRETTY_FUNCTION__' +parameter: parameterAttribute* type ('...' | (Identifier ('=' defaultInitializerExpression)?))? ; parameterAttribute: 'auto' @@ -851,6 +982,14 @@ parameterAttribute: 'auto' | typeConstructor ; +defaultInitializerExpression: assignExpression + | '__FILE__' + | '__MODULE__' + | '__LINE__' + | '__FUNCTION__' + | '__PRETTY_FUNCTION__' + ; + functionAttribute: 'nothrow' | 'pure' | atAttribute @@ -879,10 +1018,10 @@ outStatement: 'out' ('(' Identifier ')')? blockStatement bodyStatement: 'body' blockStatement ; -aliasDeclaration: 'alias' (aliasinitializer (',' aliasinitializer)* | type declarator) ';' +aliasDeclaration: 'alias' (aliasInitializer (',' aliasInitializer)* | type declarator) ';' ; -aliasinitializer: Identifier '=' type +aliasInitializer: Identifier '=' type ; variableDeclaration: type declarator (',' declarator)* ';' @@ -939,7 +1078,7 @@ protectionAttribute: 'private' | 'export' ; -traitsExpression: 'traits' '(' Identifier ',' traitsArgument (',' traitsArgument)* ')' +traitsExpression: '__traits' '(' Identifier ',' traitsArgument (',' traitsArgument)* ')' ; traitsArgument: assignExpression From 343e206b4655be447931cc430dc4fde61cb13714 Mon Sep 17 00:00:00 2001 From: Hackerpilot Date: Mon, 22 Apr 2013 23:01:03 -0700 Subject: [PATCH 6/9] Fixed several errors --- D.g4 | 25 +++++++++++++++---------- 1 file changed, 15 insertions(+), 10 deletions(-) diff --git a/D.g4 b/D.g4 index 5fa5aaa..2e50f6d 100644 --- a/D.g4 +++ b/D.g4 @@ -192,9 +192,9 @@ fragment OctalDigit: [0-7]; fragment BinDigit: [01]; fragment DecimalDigit: [0-9]; -fragment BlockComment: '/*' (Character | Whitespace)* '*/'; +fragment BlockComment: '/*' .*? '*/'; fragment LineComment: '//' (~[\r\n])* EndOfLine; -fragment NestingBlockComment: '/+' (NestingBlockComment | Character*) '+/'; +fragment NestingBlockComment: '/+' (NestingBlockComment | .)* '+/'; Comment : (BlockComment | LineComment | NestingBlockComment) -> skip; Identifier : ([a-zA-Z_])([a-zA-Z0-9_])*; @@ -227,7 +227,7 @@ fragment HexString: 'x"' HexStringChar* '"' StringPostfix?; // fragment TokenString: 'q{' Token* '}'; StringLiteral : WysiwygString | AlternativeWysiwygString | DoubleQuotedString | HexString /*| DelimitedString | TokenString*/; -CharacterLiteral: '\'' (Character | EscapeSequence) '\''; +CharacterLiteral: '\'' ( EscapeSequence | ~[\\'] )*? '\''; IntegerLiteral: Integer IntegerSuffix?; fragment Integer: BinaryInteger | DecimalInteger | HexadecimalInteger; @@ -271,6 +271,7 @@ declaration: attributedDeclaration | staticDestructor | sharedStaticDestructor | sharedStaticConstructor + | conditionalDeclaration ; importDeclaration: 'static'? 'import' importList ';' @@ -330,6 +331,7 @@ nonemptyStatement: nonEmptyStatementNoCaseNoDefault ; nonEmptyStatementNoCaseNoDefault: labeledStatement + | blockStatement | assignStatement | ifStatement | whileStatement @@ -898,10 +900,7 @@ blockStatement: '{' declarationsAndStatements? '}' declarationsAndStatements: (declaration | statement)+ ; -functionDeclaration: type Identifier parameters (functionBody | ';') - ; - -functionTemplateDeclaration: type Identifier templateParameters parameters constraint? functionBody +functionDeclaration: type Identifier (templateParameters? parameters constraint? functionBody | parameters (functionBody | ';')) ; type: typeConstructors? type2 @@ -912,10 +911,10 @@ type2: type3 typeSuffix? ; type3: builtinType - | '.' identifierChain - | identifierChain + | '.' identifierOrTemplateChain + | identifierOrTemplateChain | typeof - | typeof '.' identifierChain + | typeof '.' identifierOrTemplateChain | 'const' '(' type ')' | 'immutable' '(' type ')' | 'shared' '(' type ')' @@ -924,6 +923,9 @@ type3: builtinType | 'function' parameters memberFunctionAttributes? ; +identifierOrTemplateChain : identifierOrTemplateInstance ('.' identifierOrTemplateInstance)* + ; + typeSuffix: '*' | '[' ']' | '[' type ']' @@ -1103,6 +1105,9 @@ sharedStaticDestructor: 'shared' 'static' 'this' '(' ')' functionBody sharedStaticConstructor: 'shared' 'static' '~' 'this' '(' ')' functionBody ; +conditionalDeclaration: compileCondition (declaration | '{' declaration* '}') + ; + invariant: 'invariant' '(' ')' blockStatement ; From d5051c5807c3f47cdc8111a15da8665d8939c3a0 Mon Sep 17 00:00:00 2001 From: Hackerpilot Date: Fri, 26 Apr 2013 13:36:06 -0700 Subject: [PATCH 7/9] Fixed more errors --- D.g4 | 177 ++++++++++++++++++++++++++++++++++++++++++----------------- 1 file changed, 127 insertions(+), 50 deletions(-) diff --git a/D.g4 b/D.g4 index 2e50f6d..d9a0208 100644 --- a/D.g4 +++ b/D.g4 @@ -194,13 +194,13 @@ fragment DecimalDigit: [0-9]; fragment BlockComment: '/*' .*? '*/'; fragment LineComment: '//' (~[\r\n])* EndOfLine; -fragment NestingBlockComment: '/+' (NestingBlockComment | .)* '+/'; +fragment NestingBlockComment: '/+' (NestingBlockComment | .)*? '+/'; Comment : (BlockComment | LineComment | NestingBlockComment) -> skip; Identifier : ([a-zA-Z_])([a-zA-Z0-9_])*; fragment WysiwygString : 'r"' '"' StringPostfix?; -fragment AlternativeWysiwygString : '`' WysiwygCharacter* '`' StringPostfix?; +fragment AlternativeWysiwygString : '`' (~['`'])* '`' StringPostfix?; fragment EscapeSequence : '\\\'' | '\\"' | '\\\\' @@ -220,12 +220,13 @@ fragment EscapeSequence : '\\\'' | '\\&' Character+ ';'; fragment HexStringChar : [0-9a-fA-F] | Whitespace | EndOfLine; fragment StringPostfix : [dwc]; -fragment DoubleQuotedCharacter : EscapeSequence | ~('"' | '\''); +fragment DoubleQuotedCharacter : EscapeSequence | ~('"' | '\\' ); fragment DoubleQuotedString : '"' DoubleQuotedCharacter* '"' StringPostfix?; fragment HexString: 'x"' HexStringChar* '"' StringPostfix?; // fragment DelimitedString: 'q"' Delimiter WysiwygCharacter+ MatchingDelimiter '"'; // fragment TokenString: 'q{' Token* '}'; -StringLiteral : WysiwygString | AlternativeWysiwygString | DoubleQuotedString | HexString /*| DelimitedString | TokenString*/; +fragment StringFragment : WysiwygString | AlternativeWysiwygString | DoubleQuotedString | HexString /*| DelimitedString | TokenString*/; +StringLiteral : StringFragment (Whitespace? StringFragment)*; CharacterLiteral: '\'' ( EscapeSequence | ~[\\'] )*? '\''; @@ -238,7 +239,7 @@ fragment HexadecimalInteger: ('0x' | '0X') HexDigit (HexDigit | '_')*; FloatLiteral: (FloatOption FloatSuffix?) | (Integer (FloatSuffix | RealSuffix)? ImaginarySuffix); fragment FloatOption: DecimalFloat | HexFloat; -fragment DecimalFloat: (DecimalInteger '.' DecimalDigit*); +fragment DecimalFloat: (DecimalInteger '.' DecimalDigit*); /* BUG: can't lex a[0..1] properly */ fragment DecimalExponent: ('e' | 'E' | 'e+' | 'E+' | 'e-' | 'E-') DecimalInteger; fragment FloatSuffix: 'F' | 'f'; fragment RealSuffix: 'L'; @@ -263,10 +264,14 @@ declaration: attributedDeclaration | classDeclaration | interfaceDeclaration | unionDeclaration + | enumDeclaration | aliasDeclaration | mixinDeclaration | unittest + | staticAssertDeclaration | templateDeclaration + | constructor + | destructor | staticConstructor | staticDestructor | sharedStaticDestructor @@ -314,6 +319,15 @@ classDeclaration: 'class' Identifier (templateParameters constraint?)? (':' iden classBody: '{' (declaration | invariant)* '}' ; +invariant: 'invariant' '(' ')' blockStatement + ; + +constructor: 'this' parameters functionBody + ; + +destructor: '~' 'this' '(' ')' functionBody + ; + statement: ';' | nonemptyStatement ; @@ -324,6 +338,17 @@ interfaceDeclaration: 'interface' Identifier (templateParameters constraint?)? ( unionDeclaration: 'union' Identifier ((templateParameters constraint? structBody)? | (structBody | ';')) ; +enumDeclaration: 'enum' Identifier? (':' type )? enumBody + ; + +enumBody: ';' + | '{' enumMember (',' enumMember?)* '}' + ; + +enumMember: Identifier + | (Identifier | type) '=' assignExpression + ; + nonemptyStatement: nonEmptyStatementNoCaseNoDefault | caseStatement | caseRangeStatement @@ -353,7 +378,8 @@ nonEmptyStatementNoCaseNoDefault: labeledStatement | pragmaStatement | foreachRangeStatement | conditionalStatement - | staticAssert + | staticAssertStatement + | assertStatement | templateMixinStatement | versionSpecification | debugSpecification @@ -367,22 +393,22 @@ labeledStatement: Identifier ':' statement returnStatement: 'return' expression? ';' ; -switchStatement: 'switch' '(' expression ')' blockStatement +switchStatement: 'switch' '(' expression ')' switchBody + ; + +switchBody: '{' (statement)+ '}' ; finalSwitchStatement: 'final' switchStatement ; -caseStatement: 'case' argumentList ':' statementListNoCaseNoDefault +caseStatement: 'case' argumentList ':' declarationsAndStatements ; -caseRangeStatement: 'case' assignExpression ':' '...' 'case' assignExpression ':' statementListNoCaseNoDefault +caseRangeStatement: 'case' assignExpression ':' '...' 'case' assignExpression ':' declarationsAndStatements ; -defaultStatement: 'default' ':' statementListNoCaseNoDefault - ; - -statementListNoCaseNoDefault: statementNoCaseNoDefault statementListNoCaseNoDefault? +defaultStatement: 'default' ':' declarationsAndStatements ; statementNoCaseNoDefault: ';' @@ -395,7 +421,7 @@ continueStatement: 'continue' Identifier? ';' breakStatement: 'break' Identifier? ';' ; -gotoStatement: 'goto' Identifier ';' +gotoStatement: 'goto' (Identifier | 'default' | 'case' expression?) ';' ; withStatement: 'with' '(' (expression | symbol | templateInstance) ')' nonEmptyStatementNoCaseNoDefault @@ -415,7 +441,7 @@ catches: lastcatch lastcatch: 'catch' nonEmptyStatementNoCaseNoDefault ; -catch_: 'catch' '(' type Identifier ')' nonEmptyStatementNoCaseNoDefault +catch_: 'catch' '(' type Identifier? ')' nonEmptyStatementNoCaseNoDefault ; finally_: 'finally' nonEmptyStatementNoCaseNoDefault @@ -591,7 +617,10 @@ debugSpecification: 'debug' '=' Identifier ';' staticIfCondition: 'static' 'if' '(' assignExpression ')' ; -staticAssert: 'static' 'assert' '(' assignExpression (',' assignExpression)? ')' ';' +staticAssertStatement: 'static' assertStatement + ; + +assertStatement: assertExpression ';' ; templateMixinStatement: 'mixin' mixinTemplateName templateArguments? Identifier? ';' @@ -613,7 +642,7 @@ functionCallStatement: functionCallExpression ';' deleteStatement: deleteExpression ';' ; -assignStatement: unaryExpression assignOperator assignExpression ';' +assignStatement: unaryExpression assignOperator assignExpression (',' unaryExpression assignOperator assignExpression)* ';' | preIncDecExpression ';' | postIncDecExpression ';' ; @@ -634,15 +663,14 @@ assignOperator: '=' | '~=' ; -ifStatement: 'if' '(' expression ')' statement ('else' statement)? +ifStatement: 'if' '(' expression ')' nonEmptyStatementNoCaseNoDefault ('else' nonEmptyStatementNoCaseNoDefault)? ; -forStatement: 'for' '(' initialize expression ';' expression ')' statement - | 'for' '(' initialize ';' expression ')' statement +forStatement: 'for' '(' (declaration | statement) expression? ';' expression? ')' nonEmptyStatementNoCaseNoDefault ; initialize: ';' - | nonemptyStatement + | nonEmptyStatementNoCaseNoDefault ; foreachStatement: ('foreach' | 'foreach_reverse') '(' foreachTypeList ';' expression ')' nonEmptyStatementNoCaseNoDefault @@ -671,7 +699,7 @@ typeidExpression: 'typeid' '(' type ')' | 'typeid' '(' expression ')' ; -isExpression: 'is' '(' type Identifier? (((':' | '==') typeSpecialization (',' templateParameterList)? ))? ')' +isExpression: 'is' '(' (assignExpression | (type Identifier? ((':' | '==') typeSpecialization (',' templateParameterList)?)?)) ')' ; templateParameterList: templateParameter (','? templateParameter)* @@ -752,20 +780,25 @@ templateSingleArgument: Identifier | 'false' | 'null' | 'this' + | '__DATE__' + | '__TIME__' + | '__TIMESTAMP__' + | '__VENDOR__' + | '__VERSION__' | '__FILE__' - | '__MODULE__' | '__LINE__' + | '__MODULE__' | '__FUNCTION__' | '__PRETTY_FUNCTION__' ; -functionCallExpression: unaryExpression arguments +functionCallExpression: unaryExpression templateArguments? arguments ; arguments: '(' argumentList? ')' ; -argumentList: assignExpression (',' argumentList?)? +argumentList: assignExpression (',' assignExpression?)* ; newExpression: 'new' type ('[' assignExpression ']' | arguments)? @@ -848,11 +881,16 @@ unaryExpression: primaryExpression | newExpression | deleteExpression | castExpression + | unaryExpression templateArguments? arguments /*functionCallExpression*/ /* This causes an error in ANTLR */ | unaryExpression ('++'| '--') /* postIncDecExpression */ /* This causes an error in ANTLR */ | unaryExpression '[' ']' | unaryExpression '[' argumentList ']' | unaryExpression '[' assignExpression '..' assignExpression ']' | unaryExpression '.' identifierOrTemplateInstance + | assertExpression + ; + +assertExpression: 'assert' '(' assignExpression (',' assignExpression)? ')' ; postIncDecExpression: unaryExpression ('++' | '--') @@ -866,14 +904,20 @@ primaryExpression: identifierOrTemplateInstance | type '.' Identifier | typeofExpression | typeidExpression + | '$' | 'this' | 'super' | 'null' | 'true' | 'false' + | '__DATE__' + | '__TIME__' + | '__TIMESTAMP__' + | '__VENDOR__' + | '__VERSION__' | '__FILE__' - | '__MODULE__' | '__LINE__' + | '__MODULE__' | '__FUNCTION__' | '__PRETTY_FUNCTION__' | IntegerLiteral @@ -885,10 +929,13 @@ primaryExpression: identifierOrTemplateInstance | '(' expression ')' | isExpression | lambdaExpression + | functionLiteralExpression | traitsExpression + | mixinExpression + | importExpression ; -whileStatement: 'while' '(' expression ')' blockStatement +whileStatement: 'while' '(' expression ')' statementNoCaseNoDefault ; doStatement: 'do' blockStatement 'while' '(' expression ')' ';' @@ -897,10 +944,10 @@ doStatement: 'do' blockStatement 'while' '(' expression ')' ';' blockStatement: '{' declarationsAndStatements? '}' ; -declarationsAndStatements: (declaration | statement)+ +declarationsAndStatements: (declaration | statementNoCaseNoDefault)+ ; -functionDeclaration: type Identifier (templateParameters? parameters constraint? functionBody | parameters (functionBody | ';')) +functionDeclaration: memberFunctionAttributes? (type | 'auto' 'ref'? | 'ref' 'auto'?) Identifier (templateParameters parameters memberFunctionAttributes? constraint? functionBody | parameters memberFunctionAttributes? (functionBody | ';')) ; type: typeConstructors? type2 @@ -919,8 +966,6 @@ type3: builtinType | 'immutable' '(' type ')' | 'shared' '(' type ')' | 'inout' '(' type ')' - | 'delegate' parameters memberFunctionAttributes? - | 'function' parameters memberFunctionAttributes? ; identifierOrTemplateChain : identifierOrTemplateInstance ('.' identifierOrTemplateInstance)* @@ -930,6 +975,7 @@ typeSuffix: '*' | '[' ']' | '[' type ']' | '[' assignExpression ']' + | ('delegate' | 'function') parameters memberFunctionAttributes? ; builtinType: 'bool' @@ -963,6 +1009,7 @@ typeConstructor: 'const' | 'immutable' | 'inout' | 'shared' + | 'ref' ; typeof: 'typeof' '(' (expression | 'return') ')' @@ -971,7 +1018,7 @@ typeof: 'typeof' '(' (expression | 'return') ')' parameters: '(' (parameter (',' parameter)*)? ')' ; -parameter: parameterAttribute* type ('...' | (Identifier ('=' defaultInitializerExpression)?))? +parameter: parameterAttribute* type (Identifier? '...' | (Identifier ('=' defaultInitializerExpression)?))? ; parameterAttribute: 'auto' @@ -1026,13 +1073,37 @@ aliasDeclaration: 'alias' (aliasInitializer (',' aliasInitializer)* | type decla aliasInitializer: Identifier '=' type ; -variableDeclaration: type declarator (',' declarator)* ';' +variableDeclaration: storageClass? type declarator (',' declarator)* ';' + | autoDeclaration ; -declarator: Identifier ('=' initializer)? +autoDeclaration: storageClass Identifier '=' initializer (',' Identifier '=' initializer)* ';' ; -mixinDeclaration: 'mixin' '(' assignExpression ')' ';' +storageClass : 'abstract' + | 'auto' + | typeConstructor + | 'deprecated' + | 'enum' + | 'extern' + | 'final' + | 'nothrow' + | 'override' + | 'pure' + | '__gshared' + | atAttribute + | 'scope' + | 'static' + | 'synchronized' + ; + +declarator: Identifier declaratorSuffix? ('=' initializer)? + ; + +declaratorSuffix: '[' (type | assignExpression)? ']' + ; + +mixinDeclaration: mixinExpression ';' ; identifierList: Identifier (',' Identifier)* @@ -1061,6 +1132,9 @@ attribute: linkageattribute | 'shared' | 'immutable' | 'inout' + | 'static' + | 'pure' + | 'nothrow' | atAttribute ; @@ -1087,9 +1161,18 @@ traitsArgument: assignExpression | type ; +mixinExpression: 'mixin' '(' assignExpression ')' + ; + +importExpression: 'import' '(' assignExpression ')' + ; + unittest: 'unittest' blockStatement ; +staticAssertDeclaration: staticAssertStatement + ; + templateDeclaration: 'template' Identifier templateParameters constraint? '{' declaration+ '}' ; @@ -1105,30 +1188,22 @@ sharedStaticDestructor: 'shared' 'static' 'this' '(' ')' functionBody sharedStaticConstructor: 'shared' 'static' '~' 'this' '(' ')' functionBody ; -conditionalDeclaration: compileCondition (declaration | '{' declaration* '}') - ; - -invariant: 'invariant' '(' ')' blockStatement +conditionalDeclaration: compileCondition (declaration | '{' declaration* '}') ('else' (declaration | '{' declaration* '}'))? ; arrayinitializer: '[' arraymemberinitializations? ']' ; -arraymemberinitializations: arraymemberinitialization - | arraymemberinitialization ',' - | arraymemberinitialization ',' arraymemberinitializations +arraymemberinitializations: arraymemberinitialization (',' arraymemberinitializations?)* ; arraymemberinitialization: (assignExpression ':')? nonVoidInitializer ; -initializer: voidinitializer +initializer: 'void' | nonVoidInitializer ; -voidinitializer: 'void' - ; - nonVoidInitializer: assignExpression | arrayinitializer | structinitializer @@ -1137,13 +1212,16 @@ nonVoidInitializer: assignExpression structinitializer: '{' structMemberInitializers? '}' ; -structMemberInitializers: structMemberInitializer (','? structMemberInitializers)? +structMemberInitializers: structMemberInitializer (',' structMemberInitializer?)* ; structMemberInitializer: (Identifier ':')? nonVoidInitializer ; -lambdaExpression: (Identifier | parameters functionAttribute? ) '=>' assignExpression +lambdaExpression: (Identifier | parameters functionAttribute* ) '=>' assignExpression + ; + +functionLiteralExpression: (('function' | 'delegate') type?)? (parameters functionAttribute*)? functionBody ; arrayLiteral: '[' argumentList ']' @@ -1152,8 +1230,7 @@ arrayLiteral: '[' argumentList ']' assocArrayLiteral: '[' keyValuePairs ']' ; -keyValuePairs: keyValuePair - | keyValuePair ',' keyValuePairs +keyValuePairs: keyValuePair (',' keyValuePair)* ; keyValuePair: assignExpression ':' assignExpression From 232b13cf623704920234e0a9e80ea278392ffd67 Mon Sep 17 00:00:00 2001 From: Hackerpilot Date: Sun, 28 Apr 2013 14:34:54 -0700 Subject: [PATCH 8/9] Fixed more errors --- D.g4 | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/D.g4 b/D.g4 index d9a0208..f431b43 100644 --- a/D.g4 +++ b/D.g4 @@ -237,7 +237,7 @@ fragment DecimalInteger: DecimalDigit (DecimalDigit | '_')*; fragment BinaryInteger: ('0b' | '0B') BinDigit (BinDigit | '_')*; fragment HexadecimalInteger: ('0x' | '0X') HexDigit (HexDigit | '_')*; -FloatLiteral: (FloatOption FloatSuffix?) | (Integer (FloatSuffix | RealSuffix)? ImaginarySuffix); +FloatLiteral: (FloatOption (FloatSuffix | RealSuffix)?) | (Integer (FloatSuffix | RealSuffix)? ImaginarySuffix); fragment FloatOption: DecimalFloat | HexFloat; fragment DecimalFloat: (DecimalInteger '.' DecimalDigit*); /* BUG: can't lex a[0..1] properly */ fragment DecimalExponent: ('e' | 'E' | 'e+' | 'E+' | 'e-' | 'E-') DecimalInteger; @@ -277,6 +277,7 @@ declaration: attributedDeclaration | sharedStaticDestructor | sharedStaticConstructor | conditionalDeclaration + | pragmaDeclaration ; importDeclaration: 'static'? 'import' importList ';' @@ -375,7 +376,6 @@ nonEmptyStatementNoCaseNoDefault: labeledStatement | throwStatement | scopeGuardStatement | asmStatement - | pragmaStatement | foreachRangeStatement | conditionalStatement | staticAssertStatement @@ -562,10 +562,10 @@ asmtypeprefix: Identifier Identifier | 'real' Identifier ; -pragmaStatement: pragma ';' +pragmaDeclaration: pragmaExpression ';' ; -pragma: 'pragma' '(' Identifier (',' argumentList)? ')' +pragmaExpression: 'pragma' '(' Identifier (',' argumentList)? ')' ; foreachRangeStatement: 'foreach' '(' foreachType ';' expression '..' expression ')' nonEmptyStatementNoCaseNoDefault @@ -1015,7 +1015,7 @@ typeConstructor: 'const' typeof: 'typeof' '(' (expression | 'return') ')' ; -parameters: '(' (parameter (',' parameter)*)? ')' +parameters: '(' ((parameter (',' parameter)*)? (',' '...')? | '...') ')' ; parameter: parameterAttribute* type (Identifier? '...' | (Identifier ('=' defaultInitializerExpression)?))? @@ -1117,7 +1117,7 @@ attributedDeclaration: attribute (':' | declaration | '{' declaration* '}') attribute: linkageattribute | alignattribute - | pragma + | pragmaExpression | protectionAttribute | 'deprecated' | 'extern' From a53f8319f8b57f4d849f9dac963eba7160b6f8b1 Mon Sep 17 00:00:00 2001 From: Hackerpilot Date: Sun, 28 Apr 2013 16:15:50 +0000 Subject: [PATCH 9/9] Fixed import declaarations and deprecation attributes --- D.g4 | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) diff --git a/D.g4 b/D.g4 index f431b43..bdc95a9 100644 --- a/D.g4 +++ b/D.g4 @@ -290,10 +290,7 @@ importList: singleImport (',' importList)? singleImport: (Identifier '=')? identifierChain ; -importBindings: singleImport ':' importBindList - ; - -importBindList: importBind (',' importBind)? +importBindings: singleImport ':' importBind (',' importBind)* ; importBind: Identifier ('=' Identifier)? @@ -427,8 +424,7 @@ gotoStatement: 'goto' (Identifier | 'default' | 'case' expression?) ';' withStatement: 'with' '(' (expression | symbol | templateInstance) ')' nonEmptyStatementNoCaseNoDefault ; -synchronizedStatement: 'synchronized' nonEmptyStatementNoCaseNoDefault - | 'synchronized' '(' expression ')' nonEmptyStatementNoCaseNoDefault +synchronizedStatement: 'synchronized' ('(' expression ')')? nonEmptyStatementNoCaseNoDefault ; tryStatement: 'try' nonEmptyStatementNoCaseNoDefault (catches | catches finally_ | finally_) @@ -1119,7 +1115,7 @@ attribute: linkageattribute | alignattribute | pragmaExpression | protectionAttribute - | 'deprecated' + | deprecated | 'extern' | 'final' | 'synchronized' @@ -1154,6 +1150,9 @@ protectionAttribute: 'private' | 'export' ; +deprecated: 'deprecated' ('(' assignExpression ')')? + ; + traitsExpression: '__traits' '(' Identifier ',' traitsArgument (',' traitsArgument)* ')' ;