diff --git a/stdx/d/parser.d b/stdx/d/parser.d index 3b1830e..05e8354 100644 --- a/stdx/d/parser.d +++ b/stdx/d/parser.d @@ -1,5 +1,13 @@ // Written in the D programming language +/** + * MACROS: + * GRAMMAR =
$0+ * RULEDEF = $(B $(DDOC_ANCHOR $0) $0) + * RULE = $(LINK2 #$0, $0) + * LITERAL = $(D_STRING $(I $0)) + */ + module stdx.d.parser; import stdx.d.lexer; @@ -17,6 +25,7 @@ import std.string : format; /** * Params: * tokens = the tokens parsed by std.d.lexer + * fileName = the name of the file being parsed * messageFunction = a function to call on error or warning messages. * The parameters are the file name, line number, column number, * the error or warning message, and a boolean (true means error, false diff --git a/stdx/d/parser.html b/stdx/d/parser.html new file mode 100644 index 0000000..8ba7bbb --- /dev/null +++ b/stdx/d/parser.html @@ -0,0 +1,2201 @@ + + +
const(Token)[] tokens | +the tokens parsed by std.d.lexer |
string fileName | +the name of the file being parsed |
void function(string, size_t, size_t, string, bool) messageFunction | +a function to call on error or warning messages. + The parameters are the file name, line number, column number, + the error or warning message, and a boolean (true means error, false + means warning). |
addExpression: + mulExpression + | addExpression ('+' | '-' | '~') mulExpression + ;
aliasDeclaration: + 'alias' aliasInitializer (',' aliasInitializer)* ';' + | 'alias' type identifier ';' + ;
aliasInitializer: + Identifier '=' type + ;
aliasThisDeclaration: + 'alias' Identifier 'this' ';' + ;
alignAttribute: + 'align' ('(' IntegerLiteral ')')? + ;
andAndExpression: + orExpression + | andAndExpression '&&' orExpression + ;
andExpression: + cmpExpression + | andExpression '&' cmpExpression + ;
argumentList: + assignExpression (',' assignExpression?)* + ;
arguments: + '(' argumentList? ')' + ;
arrayInitializer: + '[' ']' + | '[' arrayMemberInitialization (',' arrayMemberInitialization?)* ']' + ;
arrayLiteral: + '[' (assignExpression (',' assignExpression)*)? ']' + ;
arrayMemberInitialization: + (assignExpression ':')? nonVoidInitializer + ;
asmAddExp: + asmMulExp + | asmAddExp ('+' | '-') asmMulExp + ;
asmAndExp: + asmEqualExp ('&' asmEqualExp)? + ;
asmBrExp: + asmUnaExp + | asmBrExp '[' asmExp ']' + ;
asmEqualExp: + asmRelExp (('==' | '!=') asmRelExp)? + ;
asmExp: + asmLogOrExp ('?' asmExp ':' asmExp)? + ;
asmInstruction: + Identifier + | 'align' IntegerLiteral + | 'align' Identifier + | Identifier ':' asmInstruction + | Identifier asmExp + | Identifier operands + ;
asmLogAndExp: + asmOrExp ('&&' asmOrExp)? + ;
asmLogOrExp: + asmLogAndExp ('||' asmLogAndExp)? + ;
asmMulExp: + asmBrExp (('*' | '/' | '%') asmBrExp)? + ;
asmOrExp: + asmXorExp ('|' asmXorExp)? + ;
asmPrimaryExp: + IntegerLiteral + | FloatLiteral + | register + | identifierChain + | '$' + ;
asmRelExp: + asmShiftExp (('<' | '<=' | '>' | '>=') asmShiftExp)? + ;
asmShiftExp: + asmAddExp (('<<' | '>>' | '>>>') asmAddExp)? + ;
asmStatement: + 'asm' '{' asmInstruction+ '}' + ;
asmTypePrefix: + Identifier Identifier + | 'byte' Identifier + | 'short' Identifier + | 'int' Identifier + | 'float' Identifier + | 'double' Identifier + | 'real' Identifier + ;
asmUnaExp: + asmTypePrefix asmExp + | Identifier asmExp + | '+' asmUnaExp + | '-' asmUnaExp + | '!' asmUnaExp + | '~' asmUnaExp + | asmPrimaryExp + ;
asmXorExp: + asmAndExp ('^' asmAndExp)? + ;
assertExpression: + 'assert' '(' assignExpression (',' assignExpression)? ')' + ;
assignExpression: + ternaryExpression (assignOperator assignExpression)? + ; + assignOperator: + '=' + | '>>>=' + | '>>=' + | '<<=' + | '+=' + | '-=' + | '*=' + | '%=' + | '&=' + | '/=' + | '|=' + | '^^=' + | '^=' + | '~=' + ;
assocArrayLiteral: + '[' keyValuePairs ']' + ;
atAttribute: + '@' (Identifier | '(' argumentList ')' | functionCallExpression) + ;
attribute: + alignAttribute + | linkageAttribute + | pragmaExpression + | storageClass + | 'export' + | 'package' + | 'private' + | 'protected' + | 'public' + ;
attributeDeclaration: + attribute ':' + ;
autoDeclaration: + storageClass Identifier '=' initializer (',' Identifier '=' initializer)* ';' + ;
blockStatement: + '{' declarationsAndStatements? '}' + ;
bodyStatement: + 'body' blockStatement + ;
breakStatement: + 'break' Identifier? ';' + ;
baseClass: + (typeofExpression '.')? identifierOrTemplateChain + ;
baseClassList: + baseClass (',' baseClass)* + ;
builtinType: + 'bool' + | 'byte' + | 'ubyte' + | 'short' + | 'ushort' + | 'int' + | 'uint' + | 'long' + | 'ulong' + | 'char' + | 'wchar' + | 'dchar' + | 'float' + | 'double' + | 'real' + | 'ifloat' + | 'idouble' + | 'ireal' + | 'cfloat' + | 'cdouble' + | 'creal' + | 'void' + ;
caseRangeStatement: + 'case' assignExpression ':' '...' 'case' assignExpression ':' declarationsAndStatements + ;
caseStatement: + 'case' argumentList ':' declarationsAndStatements + ;
castExpression: + 'cast' '(' (type | castQualifier)? ')' unaryExpression + ;
castQualifier: + 'const' + | 'const' 'shared' + | 'immutable' + | 'inout' + | 'inout' 'shared' + | 'shared' + | 'shared' 'const' + | 'shared' 'inout' + ;
catch: + 'catch' '(' type Identifier? ')' declarationOrStatement + ;
catches: + catch+ + | catch* lastCatch + ;
classDeclaration: + 'class' Identifier (templateParameters constraint?)? (':' baseClassList)? structBody + ;
cmpExpression: + shiftExpression + | equalExpression + | identityExpression + | relExpression + | inExpression + ;
compileCondition: + versionCondition + | debugCondition + | staticIfCondition + ;
conditionalDeclaration: + compileCondition declaration + | compileCondition ':' declaration+ + | compileCondition declaration ('else' declaration)? + ;
conditionalStatement: + compileCondition declarationOrStatement ('else' declarationOrStatement)? + ;
constraint: + 'if' '(' expression ')' + ;
constructor: + 'this' templateParameters parameters memberFunctionAttribute* constraint? (functionBody | ';') + ;
continueStatement: + 'continue' Identifier? ';' + ;
debugCondition: + 'debug' ('(' (IntegerLiteral | Identifier) ')')? + ;
debugSpecification: + 'debug' '=' (Identifier | IntegerLiteral) ';' + ;
declaration: + attribute* + ; + declaration2: + aliasDeclaration + | aliasThisDeclaration + | classDeclaration + | conditionalDeclaration + | constructor + | destructor + | enumDeclaration + | functionDeclaration + | importDeclaration + | interfaceDeclaration + | mixinDeclaration + | mixinTemplateDeclaration + | pragmaDeclaration + | sharedStaticConstructor + | sharedStaticDestructor + | staticAssertDeclaration + | staticConstructor + | staticDestructor + | structDeclaration + | templateDeclaration + | unionDeclaration + | unittest + | variableDeclaration + | attributeDeclaration + | invariant + | '{' declaration+ '}' + ;
declarationsAndStatements: + declarationOrStatement+ + ;
declarationOrStatement: + declaration + | statement + ;
declarator: + Identifier ('=' initializer)? + ;
defaultStatement: + 'default' ':' declarationsAndStatements + ;
deleteExpression: + 'delete' unaryExpression + ;
deprecated: + 'deprecated' ('(' assignExpression ')')? + ;
destructor: + '~' 'this' '(' ')' (functionBody | ';') + ;
doStatement: + 'do' statementNoCaseNoDefault 'while' '(' expression ')' ';' + ;
enumBody: + ';' + | '{' enumMember (',' enumMember?)* '}' + ;
enumDeclaration: + 'enum' Identifier? (':' type)? enumBody + ;
enumMember: + Identifier + | (Identifier | type) '=' assignExpression + ;
equalExpression: + shiftExpression ('==' | '!=') shiftExpression + ;
expression: + assignExpression (',' assignExpression)* + ;
expressionStatement: + expression ';' + ;
finalSwitchStatement: + 'final' switchStatement + ;
finally: + 'finally' declarationOrStatement + ;
forStatement: + 'for' '(' declarationOrStatement expression? ';' expression? ')' declarationOrStatement + ;
foreachStatement: + ('foreach' | 'foreach_reverse') '(' foreachTypeList ';' expression ')' declarationOrStatement + | ('foreach' | 'foreach_reverse') '(' foreachType ';' expression '..' expression ')' declarationOrStatement + ;
foreachType: + typeConstructors? type? Identifier + ;
foreachTypeList: + foreachType (',' foreachType)* + ;
functionAttribute: + atAttribute + | 'pure' + | 'nothrow' + ;
functionBody: + blockStatement + | (inStatement | outStatement | outStatement inStatement | inStatement outStatement)? bodyStatement + ;
functionCallExpression: + unaryExpression templateArguments? arguments + ;
functionCallStatement: + functionCallExpression ';' + ;
functionDeclaration: + (storageClass | type) Identifier templateParameters parameters memberFunctionAttribute* constraint? (functionBody | ';') + ;
functionLiteralExpression: + (('function' | 'delegate') type?)? (parameters functionAttribute*)? functionBody + ;
gotoStatement: + 'goto' (Identifier | 'default' | 'case' expression?) ';' + ;
identifierChain: + Identifier ('.' Identifier)* + ;
identifierList: + Identifier (',' Identifier)* + ;
identifierOrTemplateChain: + identifierOrTemplateInstance ('.' identifierOrTemplateInstance)* + ;
identifierOrTemplateInstance: + Identifier + | templateInstance + ;
identityExpression: + shiftExpression ('is' | '!' 'is') shiftExpression + ;
ifStatement: + 'if' '(' ifCondition ')' declarationOrStatement ('else' declarationOrStatement)? + ifCondition: + 'auto' Identifier '=' expression + | type Identifier '=' expression + | expression + ;
importBind: + Identifier ('=' Identifier)? + ;
importBindings: + singleImport ':' importBind (',' importBind)* + ;
importDeclaration: + 'import' singleImport (',' singleImport)* (',' importBindings)? ';' + | 'import' importBindings ';' + ;
importExpression: + 'import' '(' assignExpression ')' + ;
indexExpression: + unaryExpression '[' argumentList ']' + ;
inExpression: + shiftExpression ('in' | '!' 'in') shiftExpression + ;
inStatement: + 'in' blockStatement + ;
initialize: + ';' + | statementNoCaseNoDefault + ;
initializer: + 'void' + | nonVoidInitializer + ;
interfaceDeclaration: + 'interface' Identifier (templateParameters constraint?)? (':' baseClassList)? structBody + ;
invariant: + 'invariant' ('(' ')')? blockStatement + ;
isExpression: + 'is' '(' type Identifier? ((':' | '==') typeSpecialization (',' templateParameterList)?)? ')' + ;
keyValuePair: + assignExpression ':' assignExpression + ;
keyValuePairs: + keyValuePair (',' keyValuePair)* ','? + ;
labeledStatement: + Identifier ':' declarationOrStatement + ;
lambdaExpression: + Identifier '=>' assignExpression + | 'function' parameters functionAttribute* '=>' assignExpression + | 'delegate' parameters functionAttribute* '=>' assignExpression + | parameters functionAttribute* '=>' assignExpression + ;
lastCatch: + 'catch' statementNoCaseNoDefault + ;
linkageAttribute: + 'extern' '(' Identifier '++'? ')' + ;
memberFunctionAttribute: + functionAttribute + | 'immutable' + | 'inout' + | 'shared' + | 'const' + ;
mixinDeclaration: + mixinExpression ';' + | templateMixinExpression ';' + ;
mixinExpression: + 'mixin' '(' assignExpression ')' + ;
mixinTemplateDeclaration: + 'mixin' templateDeclaration + ;
mixinTemplateName: + symbol + | typeofExpression '.' identifierOrTemplateChain + ;
module: + moduleDeclaration? declaration* + ;
moduleDeclaration: + 'module' identifierChain ';' + ;
mulExpression: + powExpression + | mulExpression ('*' | '/' | '%') powExpression + ;
newAnonClassExpression: + 'new' arguments? 'class' arguments? baseClassList? structBody + ;
newExpression: + 'new' type ('[' assignExpression ']' | arguments)? + | newAnonClassExpression + ;
statementNoCaseNoDefault: + labeledStatement + | blockStatement + | ifStatement + | whileStatement + | doStatement + | forStatement + | foreachStatement + | switchStatement + | finalSwitchStatement + | continueStatement + | breakStatement + | returnStatement + | gotoStatement + | withStatement + | synchronizedStatement + | tryStatement + | throwStatement + | scopeGuardStatement + | asmStatement + | conditionalStatement + | staticAssertStatement + | versionSpecification + | debugSpecification + | expressionStatement + ;
nonVoidInitializer: + assignExpression + | arrayInitializer + | structInitializer + ;
operands: + asmExp+ + ;
orExpression: + xorExpression + | orExpression '|' xorExpression + ;
orOrExpression: + andAndExpression + | orOrExpression '||' andAndExpression + ;
outStatement: + 'out' ('(' Identifier ')')? blockStatement + ;
parameter: + parameterAttribute* type (Identifier? '...' | (Identifier? ('=' assignExpression)?))? + ;
parameterAttribute: + typeConstructor + | 'final' + | 'in' + | 'lazy' + | 'out' + | 'ref' + | 'scope' + | 'auto' + ;
parameters: + '(' parameter (',' parameter)* (',' '...')? ')' + | '(' '...' ')' + | '(' ')' + ;
postblit: + 'this' '(' 'this' ')' (functionBody | ';') + ;
postIncDecExpression: + unaryExpression ('++' | '--') + ;
powExpression: + unaryExpression + | powExpression '^^' unaryExpression + ;
pragmaDeclaration: + pragmaExpression ';' + ;
pragmaExpression: + 'pragma' '(' Identifier (',' argumentList)? ')' + ;
preIncDecExpression: + ('++' | '--') unaryExpression + ;
primaryExpression: + identifierOrTemplateInstance + | '.' identifierOrTemplateInstance + | basicType '.' Identifier + | typeofExpression + | typeidExpression + | vector + | arrayLiteral + | assocArrayLiteral + | '(' expression ')' + | isExpression + | lambdaExpression + | functionLiteralExpression + | traitsExpression + | mixinExpression + | importExpression + | '$' + | 'this' + | 'super' + | 'null' + | 'true' + | 'false' + | '__DATE__' + | '__TIME__' + | '__TIMESTAMP__' + | '__VENDOR__' + | '__VERSION__' + | '__FILE__' + | '__LINE__' + | '__MODULE__' + | '__FUNCTION__' + | '__PRETTY_FUNCTION__' + | IntegerLiteral + | FloatLiteral + | StringLiteral+ + | CharacterLiteral + ;
register: + Identifier + | Identifier '(' IntegerLiteral ')' + ;
relExpression: + shiftExpression + | relExpression relOperator shiftExpression + ; + relOperator: + '<' + | '<=' + | '>' + | '>=' + | '!<>=' + | '!<>' + | '<>' + | '<>=' + | '!>' + | '!>=' + | '!<' + | '!<=' + ;
returnStatement: + 'return' expression? ';' + ;
scopeGuardStatement: + 'scope' '(' Identifier ')' statementNoCaseNoDefault + ;
sharedStaticConstructor: + 'shared' 'static' 'this' '(' ')' functionBody + ;
sharedStaticDestructor: + 'shared' 'static' '~' 'this' '(' ')' functionBody + ;
shiftExpression: + addExpression + | shiftExpression ('<<' | '>>' | '>>>') addExpression + ;
singleImport: + (Identifier '=')? identifierChain + ;
sliceExpression: + unaryExpression '[' assignExpression '..' assignExpression ']' + | unaryExpression '[' ']' + ;
statement: + statementNoCaseNoDefault + | caseStatement + | caseRangeStatement + | defaultStatement + ;
staticAssertDeclaration: + staticAssertStatement + ;
staticAssertStatement: + 'static' assertExpression ';' + ;
staticConstructor: + 'static' 'this' '(' ')' functionBody + ;
staticDestructor: + 'static' '~' 'this' '(' ')' functionBody + ;
staticIfCondition: + 'static' 'if' '(' assignExpression ')' + ;
storageClass: + atAttribute + | typeConstructor + | deprecated + | 'abstract' + | 'auto' + | 'enum' + | 'extern' + | 'final' + | 'nothrow' + | 'override' + | 'pure' + | 'ref' + | '__gshared' + | 'scope' + | 'static' + | 'synchronized' + ;
structBody: + '{' declaration* '}' + ;
structDeclaration: + 'struct' Identifier? (templateParameters constraint? structBody | (structBody | ';')) + ;
structInitializer: + '{' structMemberInitializers? '}' + ;
structMemberInitializer: + (Identifier ':')? nonVoidInitializer + ;
structMemberInitializers: + structMemberInitializer (',' structMemberInitializer?)* + ;
switchStatement: + 'switch' '(' expression ')' statement + ;
symbol: + '.'? identifierOrTemplateChain + ;
synchronizedStatement: + 'synchronized' ('(' expression ')')? statementNoCaseNoDefault + ;
templateAliasParameter: + 'alias' type? Identifier (':' (type | assignExpression))? ('=' (type | assignExpression))? + ;
templateArgument: + type + | assignExpression + ;
templateArgumentList: + templateArgument (',' templateArgument?)* + ;
templateArguments: + '!' ('(' templateArgumentList? ')' | templateSingleArgument) + ;
templateDeclaration: + 'template' Identifier templateParameters constraint? '{' declaration* '}' + | eponymousTemplateDeclaration + ;
eponymousTemplateDeclaration: + 'enum' Identifier templateParameters '=' assignExpression ';' + ;
templateInstance: + Identifier templateArguments + ;
templateMixinExpression: + 'mixin' mixinTemplateName templateArguments? Identifier? + ;
templateParameter: + templateTypeParameter + | templateValueParameter + | templateAliasParameter + | templateTupleParameter + | templateThisParameter + ;
templateParameterList: + templateParameter (',' templateParameter?)* + ;
templateParameters: + '(' templateParameterList? ')' + ;
templateSingleArgument: + builtinType + | Identifier + | CharacterLiteral + | StringLiteral + | IntegerLiteral + | FloatLiteral + | 'true' + | 'false' + | 'null' + | 'this' + | '__DATE__' + | '__TIME__' + | '__TIMESTAMP__' + | '__VENDOR__' + | '__VERSION__' + | '__FILE__' + | '__LINE__' + | '__MODULE__' + | '__FUNCTION__' + | '__PRETTY_FUNCTION__' + ;
templateThisParameter: + 'this' templateTypeParameter + ;
templateTupleParameter: + Identifier '...' + ;
templateTypeParameter: + Identifier (':' type)? ('=' type)? + ;
templateValueParameter: + type Identifier (':' expression)? templateValueParameterDefault? + ;
templateValueParameterDefault: + '=' ('__FILE__' | '__MODULE__' | '__LINE__' | '__FUNCTION__' | '__PRETTY_FUNCTION__' | assignExpression) + ;
ternaryExpression: + orOrExpression ('?' expression ':' ternaryExpression)? + ;
throwStatement: + 'throw' expression ';' + ;
traitsExpression: + '__traits' '(' Identifier ',' TemplateArgumentList ')' + ;
tryStatement: + 'try' declarationOrStatement (catches | catches finally | finally) + ;
type: + attribute? type2 typeSuffix* + ;
type2: + builtinType + | symbol + | typeofExpression ('.' identifierOrTemplateChain)? + | typeConstructor '(' type ')' + ;
typeConstructor: + 'const' + | 'immutable' + | 'inout' + | 'shared' + | 'scope' + ;
typeConstructors: + typeConstructor+ + ;
typeSpecialization: + type + | 'struct' + | 'union' + | 'class' + | 'interface' + | 'enum' + | 'function' + | 'delegate' + | 'super' + | 'const' + | 'immutable' + | 'inout' + | 'shared' + | 'return' + | 'typedef' + | '__parameters' + ;
typeSuffix: + '*' + | '[' type? ']' + | '[' assignExpression ']' + | '[' assignExpression '..' assignExpression ']' + | ('delegate' | 'function') parameters memberFunctionAttribute* + ;
typeidExpression: + 'typeid' '(' (type | expression) ')' + ;
typeofExpression: + 'typeof' '(' (expression | 'return') ')' + ;
unaryExpression: + primaryExpression + | '&' unaryExpression + | '!' unaryExpression + | '*' unaryExpression + | '+' unaryExpression + | '-' unaryExpression + | '~' unaryExpression + | '++' unaryExpression + | '--' unaryExpression + | newExpression + | deleteExpression + | castExpression + | assertExpression + | functionCallExpression + | sliceExpression + | indexExpression + | '$LPAREN' type '$RPAREN' '.' identifierOrTemplateInstance + | unaryExpression '.' identifierOrTemplateInstance + | unaryExpression '--' + | unaryExpression '++' + ;
unionDeclaration: + 'union' Identifier templateParameters constraint? structBody + | 'union' Identifier (structBody | ';') + | 'union' structBody + ;
unittest: + 'unittest' blockStatement + ;
variableDeclaration: + type declarator (',' declarator)* ';' + | autoDeclaration + ;
vector: + '__vector' '(' type ')' + ;
versionCondition: + 'version' '(' (IntegerLiteral | Identifier | 'unittest' | 'assert') ')' + ;
versionSpecification: + 'version' '=' (Identifier | IntegerLiteral) ';' + ;
whileStatement: + 'while' '(' expression ')' declarationOrStatement + ;
withStatement: + 'with' '(' expression ')' statementNoCaseNoDefault + ;
xorExpression: + andExpression + | xorExpression '^' andExpression + ;