Skip to content

Commit e2cfa3d

Browse files
committed
removed bail-out error strategy to let ANTLR recover parse errors. tests still pass, but need to tweak parser/resolver to handle parse tree nodes with a recognitionexception now.
1 parent 05f0acc commit e2cfa3d

16 files changed

+105
-38
lines changed

Rubberduck.Parsing/Preprocessing/VBAPrecompilationParser.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,8 @@ public VBAConditionalCompilationParser.CompilationUnitContext Parse(string modul
1717
var lexer = new VBALexer(stream);
1818
var tokens = new CommonTokenStream(lexer);
1919
var parser = new VBAConditionalCompilationParser(tokens);
20-
parser.AddErrorListener(new ExceptionErrorListener());
21-
VBAConditionalCompilationParser.CompilationUnitContext tree = null;
20+
//parser.AddErrorListener(new SyntaxErrorNotificationListener()); // notify?
21+
VBAConditionalCompilationParser.CompilationUnitContext tree;
2222
try
2323
{
2424
parser.Interpreter.PredictionMode = PredictionMode.Sll;

Rubberduck.Parsing/Rubberduck.Parsing.csproj

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -244,6 +244,8 @@
244244
<Compile Include="Symbols\FunctionDeclaration.cs" />
245245
<Compile Include="Symbols\SubroutineDeclaration.cs" />
246246
<Compile Include="Symbols\ProjectReferencePass.cs" />
247+
<Compile Include="Symbols\SyntaxErrorInfo.cs" />
248+
<Compile Include="Symbols\SyntaxErrorNotificationListener.cs" />
247249
<Compile Include="Symbols\TypeHierarchyPass.cs" />
248250
<Compile Include="Symbols\TypeAnnotationPass.cs" />
249251
<Compile Include="Symbols\IdentifierReferenceResolver.cs" />
@@ -284,7 +286,6 @@
284286
<Compile Include="VBA\VBADateLiteralParser.cs" />
285287
<Compile Include="VBA\VBAExpressionParser.cs" />
286288
<Compile Include="VBA\VBAModuleParser.cs" />
287-
<Compile Include="VBA\WalkerCancelledException.cs" />
288289
</ItemGroup>
289290
<ItemGroup>
290291
<None Include="Grammar\VBAParser.g4">

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -103,7 +103,7 @@ public IEnumerable<Declaration> MatchName(string name)
103103
{
104104
return result;
105105
}
106-
return new List<Declaration>();
106+
return Enumerable.Empty<Declaration>();
107107
}
108108

109109
public Declaration FindProject(string name, Declaration currentScope = null)

Rubberduck.Parsing/Symbols/ExceptionErrorListener.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
using Antlr4.Runtime;
1+
using System;
2+
using Antlr4.Runtime;
23

34
namespace Rubberduck.Parsing.Symbols
45
{

Rubberduck.Parsing/Symbols/SyntaxErrorException.cs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,9 @@ public class SyntaxErrorException : Exception
1313
{
1414
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
1515

16+
public SyntaxErrorException(SyntaxErrorInfo info)
17+
: this(info.Message, info.Exception, info.OffendingSymbol, info.LineNumber, info.Position) { }
18+
1619
public SyntaxErrorException(string message, RecognitionException innerException, IToken offendingSymbol, int line, int position)
1720
: base(message, innerException)
1821
{
Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,31 @@
1+
using Antlr4.Runtime;
2+
3+
namespace Rubberduck.Parsing.Symbols
4+
{
5+
public class SyntaxErrorInfo
6+
{
7+
public SyntaxErrorInfo(string message, RecognitionException innerException, IToken offendingSymbol, int line, int position)
8+
{
9+
_message = message;
10+
_innerException = innerException;
11+
_token = offendingSymbol;
12+
_line = line;
13+
_position = position;
14+
}
15+
16+
private readonly string _message;
17+
public string Message { get { return _message; } }
18+
19+
private readonly RecognitionException _innerException;
20+
public RecognitionException Exception { get { return _innerException; } }
21+
22+
private readonly IToken _token;
23+
public IToken OffendingSymbol { get { return _token; } }
24+
25+
private readonly int _line;
26+
public int LineNumber { get { return _line; } }
27+
28+
private readonly int _position;
29+
public int Position { get { return _position; } }
30+
}
31+
}
Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,36 @@
1+
using System;
2+
using Antlr4.Runtime;
3+
4+
namespace Rubberduck.Parsing.Symbols
5+
{
6+
public class SyntaxErrorNotificationListener : BaseErrorListener
7+
{
8+
public event EventHandler<SyntaxErrorEventArgs> OnSyntaxError;
9+
public override void SyntaxError(IRecognizer recognizer, IToken offendingSymbol, int line, int charPositionInLine, string msg, RecognitionException e)
10+
{
11+
var info = new SyntaxErrorInfo(msg, e, offendingSymbol, line, charPositionInLine);
12+
NotifySyntaxError(info);
13+
}
14+
15+
private void NotifySyntaxError(SyntaxErrorInfo info)
16+
{
17+
var handler = OnSyntaxError;
18+
if (handler != null)
19+
{
20+
handler.Invoke(this, new SyntaxErrorEventArgs(info));
21+
}
22+
}
23+
}
24+
25+
public class SyntaxErrorEventArgs : EventArgs
26+
{
27+
private readonly SyntaxErrorInfo _info;
28+
29+
public SyntaxErrorEventArgs(SyntaxErrorInfo info)
30+
{
31+
_info = info;
32+
}
33+
34+
public SyntaxErrorInfo Info { get { return _info; } }
35+
}
36+
}

Rubberduck.Parsing/VBA/AttributeParser.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponen
4747
// line numbers are offset due to module header and attributes
4848
// (these don't show up in the VBE, that's why we're parsing an exported file)
4949
ITokenStream tokenStream;
50-
new VBAModuleParser().Parse(component.Name, preprocessed, new IParseTreeListener[] { listener }, out tokenStream);
50+
new VBAModuleParser().Parse(component.Name, preprocessed, new IParseTreeListener[] { listener }, new SyntaxErrorNotificationListener(), out tokenStream);
5151
return listener.Attributes;
5252
}
5353

Rubberduck.Parsing/VBA/ComponentParseTask.cs

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -87,6 +87,7 @@ public void Start(CancellationToken token)
8787
}
8888
catch (SyntaxErrorException exception)
8989
{
90+
System.Diagnostics.Debug.Assert(false, "A RecognitionException should be notified of, not thrown as a SyntaxErrorException. This lets the parser recover from parse errors.");
9091
Logger.Error(exception, "Exception thrown in thread {0}.", Thread.CurrentThread.ManagedThreadId);
9192
var failedHandler = ParseFailure;
9293
if (failedHandler != null)
@@ -165,7 +166,19 @@ private string RewriteAndPreprocess()
165166

166167
private IParseTree ParseInternal(string moduleName, string code, IParseTreeListener[] listeners, out ITokenStream outStream)
167168
{
168-
return _parser.Parse(moduleName, code, listeners, out outStream);
169+
var errorNotifier = new SyntaxErrorNotificationListener();
170+
errorNotifier.OnSyntaxError += ParserSyntaxError;
171+
return _parser.Parse(moduleName, code, listeners, errorNotifier, out outStream);
172+
}
173+
174+
private void ParserSyntaxError(object sender, SyntaxErrorEventArgs e)
175+
{
176+
var handler = ParseFailure;
177+
if (handler != null)
178+
{
179+
var args = new ParseFailureArgs {Cause = new SyntaxErrorException(e.Info)}; // todo: refactor. exceptions should be thrown, not passed around as data
180+
handler.Invoke(this, args);
181+
}
169182
}
170183

171184
private IEnumerable<CommentNode> QualifyAndUnionComments(QualifiedModuleName qualifiedName, IEnumerable<VBAParser.CommentContext> comments, IEnumerable<VBAParser.RemCommentContext> remComments)

Rubberduck.Parsing/VBA/VBADateLiteralParser.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using Antlr4.Runtime;
22
using Antlr4.Runtime.Atn;
33
using NLog;
4-
using Rubberduck.Parsing.Symbols;
54
using System;
65
using Rubberduck.Parsing.Preprocessing;
76

@@ -22,8 +21,8 @@ public VBADateParser.DateLiteralContext Parse(string date)
2221
var lexer = new VBADateLexer(stream);
2322
var tokens = new CommonTokenStream(lexer);
2423
var parser = new VBADateParser(tokens);
25-
parser.AddErrorListener(new ExceptionErrorListener());
26-
VBADateParser.CompilationUnitContext tree = null;
24+
//parser.AddErrorListener(new SyntaxErrorNotificationListener()); // notify?
25+
VBADateParser.CompilationUnitContext tree;
2726
try
2827
{
2928
parser.Interpreter.PredictionMode = PredictionMode.Sll;

0 commit comments

Comments
 (0)