Skip to content

Commit 971c3d3

Browse files
authored
Merge pull request #2581 from retailcoder/next
ParseTask cancellation and logging
2 parents f2461d0 + 8907661 commit 971c3d3

File tree

9 files changed

+42
-38
lines changed

9 files changed

+42
-38
lines changed
Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,9 @@
1-
namespace Rubberduck.Parsing.Preprocessing
1+
using System.Threading;
2+
3+
namespace Rubberduck.Parsing.Preprocessing
24
{
35
public interface IVBAPreprocessor
46
{
5-
string Execute(string moduleName, string unprocessedCode);
7+
string Execute(string moduleName, string unprocessedCode, CancellationToken token);
68
}
79
}

Rubberduck.Parsing/Preprocessing/VBAPreprocessor.cs

Lines changed: 7 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
1-
namespace Rubberduck.Parsing.Preprocessing
1+
using System.Threading;
2+
3+
namespace Rubberduck.Parsing.Preprocessing
24
{
35
public sealed class VBAPreprocessor : IVBAPreprocessor
46
{
@@ -11,15 +13,12 @@ public VBAPreprocessor(double vbaVersion)
1113
_parser = new VBAPrecompilationParser();
1214
}
1315

14-
public string Execute(string moduleName, string unprocessedCode)
15-
{
16-
return Preprocess(moduleName, unprocessedCode);
17-
}
18-
19-
private string Preprocess(string moduleName, string unprocessedCode)
16+
public string Execute(string moduleName, string unprocessedCode, CancellationToken token)
2017
{
21-
SymbolTable<string, IValue> symbolTable = new SymbolTable<string, IValue>();
18+
token.ThrowIfCancellationRequested();
19+
var symbolTable = new SymbolTable<string, IValue>();
2220
var tree = _parser.Parse(moduleName, unprocessedCode);
21+
token.ThrowIfCancellationRequested();
2322
var stream = tree.Start.InputStream;
2423
var evaluator = new VBAPreprocessorVisitor(symbolTable, new VBAPredefinedCompilationConstants(_vbaVersion), stream);
2524
var expr = evaluator.Visit(tree);

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -488,10 +488,7 @@ public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string i
488488
public Declaration OnBracketedExpression(string expression, ParserRuleContext context)
489489
{
490490
var hostApp = FindProject(_hostApp == null ? "VBA" : _hostApp.ApplicationName);
491-
if (hostApp == null)
492-
{
493-
494-
}
491+
Debug.Assert(hostApp != null, "Host application project can't be null. Make sure VBA standard library is included if host is unknown.");
495492

496493
var qualifiedName = hostApp.QualifiedName.QualifiedModuleName.QualifyMemberName(expression);
497494

Rubberduck.Parsing/VBA/AttributeParser.cs

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
using System.Collections.Generic;
88
using System.IO;
99
using System.Linq;
10+
using System.Threading;
1011
using Rubberduck.VBEditor.SafeComWrappers;
1112
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1213

@@ -27,8 +28,10 @@ public AttributeParser(IModuleExporter exporter, Func<IVBAPreprocessor> preproce
2728
/// Exports the specified component to a temporary file, loads, and then parses the exported file.
2829
/// </summary>
2930
/// <param name="component"></param>
30-
public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponent component)
31+
/// <param name="token"></param>
32+
public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponent component, CancellationToken token)
3133
{
34+
token.ThrowIfCancellationRequested();
3235
var path = _exporter.Export(component);
3336
if (!File.Exists(path))
3437
{
@@ -37,11 +40,13 @@ public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponen
3740
}
3841
var code = File.ReadAllText(path);
3942
File.Delete(path);
43+
token.ThrowIfCancellationRequested();
44+
4045
var type = component.Type == ComponentType.StandardModule
4146
? DeclarationType.ProceduralModule
4247
: DeclarationType.ClassModule;
4348
var preprocessor = _preprocessorFactory();
44-
var preprocessed = preprocessor.Execute(component.Name, code);
49+
var preprocessed = preprocessor.Execute(component.Name, code, token);
4550
var listener = new AttributeListener(Tuple.Create(component.Name, type));
4651
// parse tree isn't usable for declarations because
4752
// line numbers are offset due to module header and attributes

Rubberduck.Parsing/VBA/ComponentParseTask.cs

Lines changed: 14 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -30,8 +30,12 @@ class ComponentParseTask
3030
public event EventHandler<ParseFailureArgs> ParseFailure;
3131
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
3232

33+
private readonly Guid _taskId;
34+
3335
public ComponentParseTask(IVBComponent vbComponent, IVBAPreprocessor preprocessor, IAttributeParser attributeParser, TokenStreamRewriter rewriter = null)
3436
{
37+
_taskId = Guid.NewGuid();
38+
3539
_attributeParser = attributeParser;
3640
_preprocessor = preprocessor;
3741
_component = vbComponent;
@@ -44,13 +48,13 @@ public void Start(CancellationToken token)
4448
{
4549
try
4650
{
47-
var code = RewriteAndPreprocess();
48-
token.ThrowIfCancellationRequested();
49-
50-
var attributes = _attributeParser.Parse(_component);
51+
Logger.Trace("Starting ParseTaskID {0} on thread {1}.", _taskId, Thread.CurrentThread.ManagedThreadId);
5152

53+
var code = RewriteAndPreprocess(token);
5254
token.ThrowIfCancellationRequested();
5355

56+
var attributes = _attributeParser.Parse(_component, token);
57+
5458
// temporal coupling... comments must be acquired before we walk the parse tree for declarations
5559
// otherwise none of the annotations get associated to their respective Declaration
5660
var commentListener = new CommentListener();
@@ -60,12 +64,13 @@ public void Start(CancellationToken token)
6064
ITokenStream stream;
6165
var tree = ParseInternal(_component.Name, code, new IParseTreeListener[]{ commentListener, annotationListener }, out stream);
6266
stopwatch.Stop();
67+
token.ThrowIfCancellationRequested();
6368

6469
var comments = QualifyAndUnionComments(_qualifiedName, commentListener.Comments, commentListener.RemComments);
6570
token.ThrowIfCancellationRequested();
6671

6772
var completedHandler = ParseCompleted;
68-
if (completedHandler != null)
73+
if (completedHandler != null && !token.IsCancellationRequested)
6974
completedHandler.Invoke(this, new ParseCompletionArgs
7075
{
7176
ParseTree = tree,
@@ -77,7 +82,7 @@ public void Start(CancellationToken token)
7782
}
7883
catch (COMException exception)
7984
{
80-
Logger.Error(exception, "Exception thrown in thread {0}.", Thread.CurrentThread.ManagedThreadId);
85+
Logger.Error(exception, "Exception thrown in thread {0}, ParseTaskID {1}.", Thread.CurrentThread.ManagedThreadId, _taskId);
8186
var failedHandler = ParseFailure;
8287
if (failedHandler != null)
8388
failedHandler.Invoke(this, new ParseFailureArgs
@@ -88,7 +93,7 @@ public void Start(CancellationToken token)
8893
catch (SyntaxErrorException exception)
8994
{
9095
//System.Diagnostics.Debug.Assert(false, "A RecognitionException should be notified of, not thrown as a SyntaxErrorException. This lets the parser recover from parse errors.");
91-
Logger.Error(exception, "Exception thrown in thread {0}.", Thread.CurrentThread.ManagedThreadId);
96+
Logger.Error(exception, "Exception thrown in thread {0}, ParseTaskID {1}.", Thread.CurrentThread.ManagedThreadId, _taskId);
9297
var failedHandler = ParseFailure;
9398
if (failedHandler != null)
9499
failedHandler.Invoke(this, new ParseFailureArgs
@@ -157,10 +162,10 @@ private static bool HasNumberedLine(string codeLine, out int? lineNumber)
157162
return false;
158163
}
159164

160-
private string RewriteAndPreprocess()
165+
private string RewriteAndPreprocess(CancellationToken token)
161166
{
162167
var code = _rewriter == null ? string.Join(Environment.NewLine, GetSanitizedCode(_component.CodeModule)) : _rewriter.GetText();
163-
var processed = _preprocessor.Execute(_component.Name, code);
168+
var processed = _preprocessor.Execute(_component.Name, code, token);
164169
return processed;
165170
}
166171

@@ -171,16 +176,6 @@ private IParseTree ParseInternal(string moduleName, string code, IParseTreeListe
171176
return _parser.Parse(moduleName, code, listeners, new ExceptionErrorListener(), out outStream);
172177
}
173178

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-
}
182-
}
183-
184179
private IEnumerable<CommentNode> QualifyAndUnionComments(QualifiedModuleName qualifiedName, IEnumerable<VBAParser.CommentContext> comments, IEnumerable<VBAParser.RemCommentContext> remComments)
185180
{
186181
var commentNodes = comments.Select(comment => new CommentNode(comment.GetComment(), Tokens.CommentMarker, new QualifiedSelection(qualifiedName, comment.GetSelection())));
Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,13 @@
11
using System;
22
using System.Collections.Generic;
3+
using System.Threading;
34
using Rubberduck.Parsing.Symbols;
45
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
56

67
namespace Rubberduck.Parsing.VBA
78
{
89
public interface IAttributeParser
910
{
10-
IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponent component);
11+
IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponent component, CancellationToken token);
1112
}
1213
}

Rubberduck.sln

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11

22
Microsoft Visual Studio Solution File, Format Version 12.00
33
# Visual Studio 2013
4-
VisualStudioVersion = 12.0.31101.0
4+
VisualStudioVersion = 12.0.40629.0
55
MinimumVisualStudioVersion = 10.0.40219.1
66
Project("{FAE04EC0-301F-11D3-BF4B-00C04F79EFBC}") = "Rubberduck", "RetailCoder.VBE\Rubberduck.csproj", "{20589DE8-432E-4359-9232-69EB070B7185}"
77
ProjectSection(ProjectDependencies) = postProject
@@ -31,6 +31,7 @@ Project("{2150E333-8FDC-42A3-9474-1A3956D46DE8}") = "Solution Items", "Solution
3131
libs\Microsoft.VB6.Interop.VBIDE.dll = libs\Microsoft.VB6.Interop.VBIDE.dll
3232
libs\Microsoft.Vbe.Interop.dll = libs\Microsoft.Vbe.Interop.dll
3333
libs\Office.dll = libs\Office.dll
34+
Performance6.psess = Performance6.psess
3435
EndProjectSection
3536
EndProject
3637
Project("{FAE04EC0-301F-11D3-BF4B-00C04F79EFBC}") = "Rubberduck.VBEditor", "Rubberduck.VBEEditor\Rubberduck.VBEditor.csproj", "{8CE35EB3-8852-4BA1-84DD-DF3F5D2967B0}"

RubberduckTests/Inspections/HostSpecificExpressionInspectionTests.cs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ public class HostSpecificExpressionInspectionTests
1717
{
1818
[TestMethod]
1919
[TestCategory("Inspections")]
20+
[DeploymentItem(@"TestFiles\")]
2021
public void ReturnsResultForExpressionOnLeftHandSide()
2122
{
2223
const string code = @"
@@ -27,6 +28,7 @@ End Sub
2728
var builder = new MockVbeBuilder();
2829
var project = builder.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
2930
.AddComponent("Module1", ComponentType.StandardModule, code)
31+
.AddReference("VBA", MockVbeBuilder.LibraryPathVBA, 4, 2, true)
3032
.AddReference("Excel", MockVbeBuilder.LibraryPathMsExcel, 1, 7, true)
3133
.Build();
3234
var vbe = builder.AddProject(project).Build();
@@ -35,6 +37,8 @@ End Sub
3537
vbe.Setup(m => m.HostApplication()).Returns(() => mockHost.Object);
3638

3739
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
40+
parser.State.AddTestLibrary("VBA.4.2.xml");
41+
parser.State.AddTestLibrary("Excel.1.8.xml");
3842
parser.Parse(new CancellationTokenSource());
3943
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
4044

RubberduckTests/Mocks/MockParser.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@ public static void ParseString(string inputCode, out QualifiedModuleName qualifi
3939
public static ParseCoordinator Create(IVBE vbe, RubberduckParserState state, string serializedDeclarationsPath = null)
4040
{
4141
var attributeParser = new Mock<IAttributeParser>();
42-
attributeParser.Setup(m => m.Parse(It.IsAny<IVBComponent>()))
42+
attributeParser.Setup(m => m.Parse(It.IsAny<IVBComponent>(), It.IsAny<CancellationToken>()))
4343
.Returns(() => new Dictionary<Tuple<string, DeclarationType>, Attributes>());
4444
return Create(vbe, state, attributeParser.Object, serializedDeclarationsPath);
4545
}

0 commit comments

Comments
 (0)