Skip to content

Commit 944e0d2

Browse files
committed
Sorted out log levels for syntax errors.
1 parent a401984 commit 944e0d2

File tree

3 files changed

+32
-14
lines changed

3 files changed

+32
-14
lines changed
Lines changed: 15 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
using System;
22
using Antlr4.Runtime;
3-
using NLog;
43

54
namespace Rubberduck.Parsing.Symbols
65
{
@@ -11,8 +10,6 @@ namespace Rubberduck.Parsing.Symbols
1110
[Serializable]
1211
public class SyntaxErrorException : Exception
1312
{
14-
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
15-
1613
public SyntaxErrorException(SyntaxErrorInfo info)
1714
: this(info.Message, info.Exception, info.OffendingSymbol, info.LineNumber, info.Position) { }
1815

@@ -22,17 +19,27 @@ public SyntaxErrorException(string message, RecognitionException innerException,
2219
_token = offendingSymbol;
2320
_line = line;
2421
_position = position;
25-
Logger.Debug(innerException == null ? "" : innerException.ToString());
26-
Logger.Debug("Token: {0} (L{1}C{2})", offendingSymbol.Text, line, position);
22+
_innerException = innerException;
2723
}
2824

2925
private readonly IToken _token;
30-
public IToken OffendingSymbol { get { return _token; } }
26+
public IToken OffendingSymbol => _token;
3127

3228
private readonly int _line;
33-
public int LineNumber { get { return _line; } }
29+
public int LineNumber => _line;
3430

3531
private readonly int _position;
36-
public int Position { get { return _position; } }
32+
public int Position => _position;
33+
34+
private readonly RecognitionException _innerException;
35+
36+
public override string ToString()
37+
{
38+
var exceptionText =
39+
$@"RecognitionException: {_innerException?.ToString() ?? string.Empty}
40+
Token: {_token.Text} (L{_line}C{_position})
41+
{base.ToString()}";
42+
return exceptionText;
43+
}
3744
}
3845
}

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 cancellationToken)
8787
}
8888
catch (COMException exception)
8989
{
90-
Logger.Error(exception, $"Exception thrown in thread {Thread.CurrentThread.ManagedThreadId} while parsing module {_qualifiedName.Name}, ParseTaskID {_taskId}.");
90+
Logger.Error(exception, $"COM Exception thrown in thread {Thread.CurrentThread.ManagedThreadId} while parsing module {_qualifiedName.Name}, ParseTaskID {_taskId}.");
9191
var failedHandler = ParseFailure;
9292
failedHandler?.Invoke(this, new ParseFailureArgs
9393
{
@@ -96,8 +96,8 @@ public void Start(CancellationToken cancellationToken)
9696
}
9797
catch (SyntaxErrorException exception)
9898
{
99-
Logger.Warn($"Syntax error; offending token '{exception.OffendingSymbol.Text}' at line {exception.LineNumber}, column {exception.Position} in module {_qualifiedName}.");
100-
Logger.Error(exception, $"Exception thrown in thread {Thread.CurrentThread.ManagedThreadId}, ParseTaskID {_taskId}.");
99+
Logger.Error($"Syntax error; offending token '{exception.OffendingSymbol.Text}' at line {exception.LineNumber}, column {exception.Position} in module {_qualifiedName}.");
100+
Logger.Debug(exception, $"SyntaxErrorException thrown in thread {Thread.CurrentThread.ManagedThreadId}, ParseTaskID {_taskId}.");
101101
var failedHandler = ParseFailure;
102102
failedHandler?.Invoke(this, new ParseFailureArgs
103103
{
@@ -115,7 +115,7 @@ public void Start(CancellationToken cancellationToken)
115115
}
116116
catch (Exception exception)
117117
{
118-
Logger.Error(exception, $"Exception thrown in thread {Thread.CurrentThread.ManagedThreadId} while parsing module {_qualifiedName.Name}, ParseTaskID {_taskId}.");
118+
Logger.Error(exception, $" Unexpected exception thrown in thread {Thread.CurrentThread.ManagedThreadId} while parsing module {_qualifiedName.Name}, ParseTaskID {_taskId}.");
119119
var failedHandler = ParseFailure;
120120
failedHandler?.Invoke(this, new ParseFailureArgs
121121
{

Rubberduck.Parsing/VBA/VBAModuleParser.cs

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using NLog;
55
using Rubberduck.Parsing.Grammar;
66
using System;
7+
using Rubberduck.Parsing.Symbols;
78

89
namespace Rubberduck.Parsing.VBA
910
{
@@ -22,9 +23,19 @@ public sealed class VBAModuleParser
2223
parser.Interpreter.PredictionMode = PredictionMode.Sll;
2324
tree = parser.startRule();
2425
}
25-
catch (Exception ex)
26+
catch (SyntaxErrorException syntaxErrorException)
2627
{
27-
Logger.Warn(ex, "SLL mode failed in module {0}. Retrying using LL.", moduleName);
28+
Logger.Warn($"SLL mode failed in module {moduleName} at symbol {syntaxErrorException.OffendingSymbol.Text} at L{syntaxErrorException.LineNumber}C{syntaxErrorException.Position}. Retrying using LL.");
29+
Logger.Debug(syntaxErrorException, "SLL mode exception");
30+
moduleTokens.Reset();
31+
parser.Reset();
32+
parser.Interpreter.PredictionMode = PredictionMode.Ll;
33+
tree = parser.startRule();
34+
}
35+
catch (Exception exception)
36+
{
37+
Logger.Warn($"SLL mode failed in module {moduleName}. Retrying using LL.");
38+
Logger.Debug(exception, "SLL mode exception");
2839
moduleTokens.Reset();
2940
parser.Reset();
3041
parser.Interpreter.PredictionMode = PredictionMode.Ll;

0 commit comments

Comments
 (0)