Skip to content

Commit

Permalink
Allow line continuations in precompiler directives
Browse files Browse the repository at this point in the history
  • Loading branch information
MDoerner committed Oct 3, 2020
1 parent 8695c05 commit 3c70bbb
Show file tree
Hide file tree
Showing 2 changed files with 85 additions and 23 deletions.
48 changes: 25 additions & 23 deletions Rubberduck.Parsing/Preprocessing/VBAConditionalCompilationParser.g4
Expand Up @@ -10,17 +10,17 @@ ccBlock :
(ccConst | ccIfBlock | physicalLine)*?
;

ccConst : WS* hashConst WS+ ccVarLhs WS* EQ WS* ccExpression ccEol;
ccConst : whiteSpace* hashConst whiteSpace+ ccVarLhs whiteSpace* EQ whiteSpace* ccExpression ccEol;
ccVarLhs : name;

ccIfBlock : ccIf ccBlock ccElseIfBlock* ccElseBlock? ccEndIf;
ccIf : WS* hashIf WS+ ccExpression WS+ THEN ccEol;
ccIf : whiteSpace* hashIf whiteSpace+ ccExpression whiteSpace+ THEN ccEol;
ccElseIfBlock : ccElseIf ccBlock;
ccElseIf : WS* hashElseIf WS+ ccExpression WS+ THEN ccEol;
ccElseIf : whiteSpace* hashElseIf whiteSpace+ ccExpression whiteSpace+ THEN ccEol;
ccElseBlock : ccElse ccBlock;
ccElse : WS* hashElse ccEol;
ccEndIf : WS* hashEndIf ccEol;
ccEol : WS* comment? (NEWLINE | EOF);
ccElse : whiteSpace* hashElse ccEol;
ccEndIf : whiteSpace* hashEndIf ccEol;
ccEol : whiteSpace* comment? (NEWLINE | EOF);
// We use parser rules instead of tokens (such as HASHCONST) because
// marked file numbers have a similar format and cause conflicts.
hashConst : HASH CONST;
Expand All @@ -32,26 +32,26 @@ hashEndIf : HASH END_IF;
physicalLine : ~(NEWLINE | EOF)* (NEWLINE | EOF);

ccExpression :
LPAREN WS* ccExpression WS* RPAREN
| ccExpression WS* POW WS* ccExpression
| MINUS WS* ccExpression
| ccExpression WS* (MULT | DIV) WS* ccExpression
| ccExpression WS* INTDIV WS* ccExpression
| ccExpression WS* MOD WS* ccExpression
| ccExpression WS* (PLUS | MINUS) WS* ccExpression
| ccExpression WS* AMPERSAND WS* ccExpression
| ccExpression WS* (EQ | NEQ | LT | GT | LEQ | GEQ | LIKE | IS) WS* ccExpression
| NOT WS* ccExpression
| ccExpression WS* AND WS* ccExpression
| ccExpression WS* OR WS* ccExpression
| ccExpression WS* XOR WS* ccExpression
| ccExpression WS* EQV WS* ccExpression
| ccExpression WS* IMP WS* ccExpression
LPAREN whiteSpace* ccExpression whiteSpace* RPAREN
| ccExpression whiteSpace* POW whiteSpace* ccExpression
| MINUS whiteSpace* ccExpression
| ccExpression whiteSpace* (MULT | DIV) whiteSpace* ccExpression
| ccExpression whiteSpace* INTDIV whiteSpace* ccExpression
| ccExpression whiteSpace* MOD whiteSpace* ccExpression
| ccExpression whiteSpace* (PLUS | MINUS) whiteSpace* ccExpression
| ccExpression whiteSpace* AMPERSAND whiteSpace* ccExpression
| ccExpression whiteSpace* (EQ | NEQ | LT | GT | LEQ | GEQ | LIKE | IS) whiteSpace* ccExpression
| NOT whiteSpace* ccExpression
| ccExpression whiteSpace* AND whiteSpace* ccExpression
| ccExpression whiteSpace* OR whiteSpace* ccExpression
| ccExpression whiteSpace* XOR whiteSpace* ccExpression
| ccExpression whiteSpace* EQV whiteSpace* ccExpression
| ccExpression whiteSpace* IMP whiteSpace* ccExpression
| intrinsicFunction
| literal
| name;

intrinsicFunction : intrinsicFunctionName LPAREN WS* ccExpression WS* RPAREN;
intrinsicFunction : intrinsicFunctionName LPAREN whiteSpace* ccExpression whiteSpace* RPAREN;

intrinsicFunctionName :
INT
Expand Down Expand Up @@ -270,4 +270,6 @@ statementKeyword :
| WEND
| WHILE
| WITH
;
;

whiteSpace : (WS | LINE_CONTINUATION)+;
60 changes: 60 additions & 0 deletions RubberduckTests/Preprocessing/VBAPreprocessorTests.cs
Expand Up @@ -27,6 +27,66 @@ public void TestPreprocessor()
}
}

[Test]
[Category("Preprocessor")]
//See issue #5294 at https://github.com/rubberduck-vba/Rubberduck/issues/5294
public void CanDealWithLineContinuationsInPrecompilerDirectives()
{
const string code = @"
Private Sub Main()
Dim a as Long: a= 10
Dim b as Long: b=5
Dim c as Long : c=a+b
#Const CCG_VERSION1 _
= _
True
#Const CCG_VERSION2 = _
False
#If CCG_VERSION1 Or _
CCG_VERSION2 Then
c=c+c
#else
c=c*c
#end if
Print c
End Sub
";
const string expectedProcessed = @"
Private Sub Main()
Dim a as Long: a= 10
Dim b as Long: b=5
Dim c as Long : c=a+b
_
_
_
_
c=c+c
Print c
End Sub
";

var actualProcessed = Parse(code);
Assert.AreEqual(expectedProcessed, actualProcessed);
}

private void AssertParseResult(string filename, string originalCode, string materializedParseTree)
{
Assert.AreEqual(originalCode, materializedParseTree, $"{filename} mismatch detected.");
Expand Down

0 comments on commit 3c70bbb

Please sign in to comment.