Skip to content

Commit f3364e9

Browse files
committed
restored bail-out parsing strategy
1 parent 078f5a4 commit f3364e9

File tree

4 files changed

+8
-7
lines changed

4 files changed

+8
-7
lines changed

Rubberduck.Parsing/Preprocessing/VBAPrecompilationParser.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ 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 SyntaxErrorNotificationListener()); // notify?
20+
parser.AddErrorListener(new ExceptionErrorListener()); // notify?
2121
VBAConditionalCompilationParser.CompilationUnitContext tree;
2222
try
2323
{

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 }, new SyntaxErrorNotificationListener(), out tokenStream);
50+
new VBAModuleParser().Parse(component.Name, preprocessed, new IParseTreeListener[] { listener }, new ExceptionErrorListener(), out tokenStream);
5151
return listener.Attributes;
5252
}
5353

Rubberduck.Parsing/VBA/ComponentParseTask.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -87,7 +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.");
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.");
9191
Logger.Error(exception, "Exception thrown in thread {0}.", Thread.CurrentThread.ManagedThreadId);
9292
var failedHandler = ParseFailure;
9393
if (failedHandler != null)
@@ -166,9 +166,9 @@ private string RewriteAndPreprocess()
166166

167167
private IParseTree ParseInternal(string moduleName, string code, IParseTreeListener[] listeners, out ITokenStream outStream)
168168
{
169-
var errorNotifier = new SyntaxErrorNotificationListener();
170-
errorNotifier.OnSyntaxError += ParserSyntaxError;
171-
return _parser.Parse(moduleName, code, listeners, errorNotifier, out outStream);
169+
//var errorNotifier = new SyntaxErrorNotificationListener();
170+
//errorNotifier.OnSyntaxError += ParserSyntaxError;
171+
return _parser.Parse(moduleName, code, listeners, new ExceptionErrorListener(), out outStream);
172172
}
173173

174174
private void ParserSyntaxError(object sender, SyntaxErrorEventArgs e)

Rubberduck.Parsing/VBA/VBADateLiteralParser.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
using NLog;
44
using System;
55
using Rubberduck.Parsing.Preprocessing;
6+
using Rubberduck.Parsing.Symbols;
67

78
namespace Rubberduck.Parsing.VBA
89
{
@@ -21,7 +22,7 @@ public VBADateParser.DateLiteralContext Parse(string date)
2122
var lexer = new VBADateLexer(stream);
2223
var tokens = new CommonTokenStream(lexer);
2324
var parser = new VBADateParser(tokens);
24-
//parser.AddErrorListener(new SyntaxErrorNotificationListener()); // notify?
25+
parser.AddErrorListener(new ExceptionErrorListener()); // notify?
2526
VBADateParser.CompilationUnitContext tree;
2627
try
2728
{

0 commit comments

Comments
 (0)