Skip to content

Commit 0bddfdb

Browse files
committed
Merge branch 'next' of https://github.com/rubberduck-vba/rubberduck into FolderAnnotationScope
2 parents 1eda58b + a401984 commit 0bddfdb

File tree

17 files changed

+171
-105
lines changed

17 files changed

+171
-105
lines changed

RetailCoder.VBE/UI/Settings/InspectionSettings.xaml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -318,7 +318,8 @@
318318
SortMemberPath="{Binding LocalizedName}">
319319
<DataGridTemplateColumn.CellTemplate>
320320
<DataTemplate>
321-
<TextBlock Text="{Binding LocalizedName}">
321+
<TextBlock Text="{Binding LocalizedName}"
322+
ToolTipService.ShowDuration="30000">
322323
<TextBlock.ToolTip>
323324
<StackPanel>
324325
<TextBlock Text="{Binding LocalizedName}"

Rubberduck.Inspections/Concrete/BooleanAssignedInIfElseInspection.cs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,12 @@ public void ClearContexts()
4848

4949
public override void ExitIfStmt(VBAParser.IfStmtContext context)
5050
{
51-
if (context.elseIfBlock().Any())
51+
if (context.elseIfBlock() != null && context.elseIfBlock().Any())
52+
{
53+
return;
54+
}
55+
56+
if (context.elseBlock() == null)
5257
{
5358
return;
5459
}
@@ -60,6 +65,7 @@ public override void ExitIfStmt(VBAParser.IfStmtContext context)
6065
}
6166

6267
// make sure the assignments are the opposite
68+
6369
if (!(ParserRuleContextHelper.GetDescendent<VBAParser.BooleanLiteralIdentifierContext>(context.block()).GetText() == Tokens.True ^
6470
ParserRuleContextHelper.GetDescendent<VBAParser.BooleanLiteralIdentifierContext>(context.elseBlock().block()).GetText() == Tokens.True))
6571
{

Rubberduck.Inspections/Inspector.cs

Lines changed: 47 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,8 @@ namespace Rubberduck.Inspections
2121
{
2222
public class Inspector : IInspector
2323
{
24+
private const int _maxDegreeOfInspectionParallelism = -1;
25+
2426
private readonly IGeneralConfigService _configService;
2527
private readonly List<IInspection> _inspections;
2628
private readonly int AGGREGATION_THRESHOLD = 128;
@@ -90,29 +92,22 @@ public async Task<IEnumerable<IInspectionResult>> FindIssuesAsync(RubberduckPars
9092
}
9193
}
9294

93-
var inspections = _inspections.Where(inspection => inspection.Severity != CodeInspectionSeverity.DoNotShow)
94-
.Select(inspection =>
95-
Task.Run(() =>
96-
{
97-
token.ThrowIfCancellationRequested();
98-
try
99-
{
100-
var inspectionResults = inspection.GetInspectionResults();
101-
102-
foreach (var inspectionResult in inspectionResults)
103-
{
104-
allIssues.Add(inspectionResult);
105-
}
106-
}
107-
catch(Exception e)
108-
{
109-
LogManager.GetCurrentClassLogger().Warn(e);
110-
}
111-
}, token)).ToList();
95+
var inspectionsToRun = _inspections.Where(inspection => inspection.Severity != CodeInspectionSeverity.DoNotShow);
11296

11397
try
11498
{
115-
await Task.WhenAll(inspections);
99+
await Task.Run(() => RunInspectionsInParallel(inspectionsToRun, allIssues, token));
100+
}
101+
catch (AggregateException exception)
102+
{
103+
if (exception.Flatten().InnerExceptions.All(ex => ex is OperationCanceledException))
104+
{
105+
LogManager.GetCurrentClassLogger().Debug("Inspections got canceled.");
106+
}
107+
else
108+
{
109+
LogManager.GetCurrentClassLogger().Error(exception);
110+
}
116111
}
117112
catch (Exception e)
118113
{
@@ -131,6 +126,38 @@ public async Task<IEnumerable<IInspectionResult>> FindIssuesAsync(RubberduckPars
131126
return results;
132127
}
133128

129+
private static void RunInspectionsInParallel(IEnumerable<IInspection> inspectionsToRun,
130+
ConcurrentBag<IInspectionResult> allIssues, CancellationToken token)
131+
{
132+
var options = new ParallelOptions
133+
{
134+
CancellationToken = token,
135+
MaxDegreeOfParallelism = _maxDegreeOfInspectionParallelism
136+
};
137+
138+
Parallel.ForEach(inspectionsToRun,
139+
options,
140+
inspection => RunInspection(inspection, allIssues)
141+
);
142+
}
143+
144+
private static void RunInspection(IInspection inspection, ConcurrentBag<IInspectionResult> allIssues)
145+
{
146+
try
147+
{
148+
var inspectionResults = inspection.GetInspectionResults();
149+
150+
foreach (var inspectionResult in inspectionResults)
151+
{
152+
allIssues.Add(inspectionResult);
153+
}
154+
}
155+
catch (Exception e)
156+
{
157+
LogManager.GetCurrentClassLogger().Warn(e);
158+
}
159+
}
160+
134161
private void WalkTrees(CodeInspectionSettings settings, RubberduckParserState state, IEnumerable<IParseTreeInspection> inspections, ParsePass pass)
135162
{
136163
var listeners = inspections

Rubberduck.Parsing/VBA/AttributeParser.cs

Lines changed: 9 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -26,18 +26,15 @@ public AttributeParser(IModuleExporter exporter, Func<IVBAPreprocessor> preproce
2626
/// Exports the specified component to a temporary file, loads, and then parses the exported file.
2727
/// </summary>
2828
/// <param name="component"></param>
29-
/// <param name="token"></param>
30-
/// <param name="stream"></param>
31-
public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponent component, CancellationToken token, out ITokenStream stream, out IParseTree tree)
29+
/// <param name="cancellationToken"></param>
30+
public (IParseTree tree, ITokenStream tokenStream, IDictionary<Tuple<string, DeclarationType>, Attributes> attributes) Parse(IVBComponent component, CancellationToken cancellationToken)
3231
{
33-
token.ThrowIfCancellationRequested();
32+
cancellationToken.ThrowIfCancellationRequested();
3433
var path = _exporter.Export(component);
3534
if (!File.Exists(path))
3635
{
3736
// a document component without any code wouldn't be exported (file would be empty anyway).
38-
stream = null;
39-
tree = null;
40-
return new Dictionary<Tuple<string, DeclarationType>, Attributes>();
37+
return (null, null, new Dictionary<Tuple<string, DeclarationType>, Attributes>());
4138
}
4239
var code = File.ReadAllText(path);
4340
try
@@ -49,24 +46,24 @@ public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponen
4946
// Meh.
5047
}
5148

52-
token.ThrowIfCancellationRequested();
49+
cancellationToken.ThrowIfCancellationRequested();
5350

5451
var type = component.Type == ComponentType.StandardModule
5552
? DeclarationType.ProceduralModule
5653
: DeclarationType.ClassModule;
5754
var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider();
5855
var tokens = tokenStreamProvider.Tokens(code);
5956
var preprocessor = _preprocessorFactory();
60-
preprocessor.PreprocessTokenStream(component.Name, tokens, token);
57+
preprocessor.PreprocessTokenStream(component.Name, tokens, cancellationToken);
6158
var listener = new AttributeListener(Tuple.Create(component.Name, type));
6259
// parse tree isn't usable for declarations because
6360
// line numbers are offset due to module header and attributes
6461
// (these don't show up in the VBE, that's why we're parsing an exported file)
6562

66-
tree = new VBAModuleParser().Parse(component.Name, tokens, new IParseTreeListener[] { listener }, new ExceptionErrorListener(), out stream);
63+
var parseResults = new VBAModuleParser().Parse(component.Name, tokens, new IParseTreeListener[] { listener }, new ExceptionErrorListener());
6764

68-
token.ThrowIfCancellationRequested();
69-
return listener.Attributes;
65+
cancellationToken.ThrowIfCancellationRequested();
66+
return (parseResults.tree, parseResults.tokenStream, listener.Attributes);
7067
}
7168
}
7269
}

Rubberduck.Parsing/VBA/ComponentParseTask.cs

Lines changed: 22 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -47,44 +47,40 @@ public ComponentParseTask(QualifiedModuleName module, IVBAPreprocessor preproces
4747
_parser = new VBAModuleParser();
4848
}
4949

50-
public void Start(CancellationToken token)
50+
public void Start(CancellationToken cancellationToken)
5151
{
5252
try
5353
{
5454
Logger.Trace($"Starting ParseTaskID {_taskId} on thread {Thread.CurrentThread.ManagedThreadId}.");
5555

56-
var tokenStream = RewriteAndPreprocess(token);
57-
token.ThrowIfCancellationRequested();
58-
59-
IParseTree attributesTree;
60-
IDictionary<Tuple<string, DeclarationType>, Attributes> attributes;
61-
var attributesTokenStream = RunAttributesPass(token, out attributesTree, out attributes);
62-
63-
var rewriter = new MemberAttributesRewriter(_exporter, _component.CodeModule, new TokenStreamRewriter(attributesTokenStream ?? tokenStream));
56+
var tokenStream = RewriteAndPreprocess(cancellationToken);
57+
cancellationToken.ThrowIfCancellationRequested();
6458

6559
// temporal coupling... comments must be acquired before we walk the parse tree for declarations
6660
// otherwise none of the annotations get associated to their respective Declaration
6761
var commentListener = new CommentListener();
6862
var annotationListener = new AnnotationListener(new VBAParserAnnotationFactory(), _qualifiedName);
6963

7064
var stopwatch = Stopwatch.StartNew();
71-
ITokenStream stream;
72-
var tree = ParseInternal(_component.Name, tokenStream, new IParseTreeListener[]{ commentListener, annotationListener }, out stream);
65+
var codePaneParseResults = ParseInternal(_component.Name, tokenStream, new IParseTreeListener[]{ commentListener, annotationListener });
7366
stopwatch.Stop();
74-
token.ThrowIfCancellationRequested();
67+
cancellationToken.ThrowIfCancellationRequested();
7568

7669
var comments = QualifyAndUnionComments(_qualifiedName, commentListener.Comments, commentListener.RemComments);
77-
token.ThrowIfCancellationRequested();
70+
cancellationToken.ThrowIfCancellationRequested();
71+
72+
var attributesPassParseResults = RunAttributesPass(cancellationToken);
73+
var rewriter = new MemberAttributesRewriter(_exporter, _component.CodeModule, new TokenStreamRewriter(attributesPassParseResults.tokenStream ?? tokenStream));
7874

7975
var completedHandler = ParseCompleted;
80-
if (completedHandler != null && !token.IsCancellationRequested)
76+
if (completedHandler != null && !cancellationToken.IsCancellationRequested)
8177
completedHandler.Invoke(this, new ParseCompletionArgs
8278
{
83-
ParseTree = tree,
84-
AttributesTree = attributesTree,
85-
Tokens = stream,
79+
ParseTree = codePaneParseResults.tree,
80+
AttributesTree = attributesPassParseResults.tree,
81+
Tokens = codePaneParseResults.tokenStream,
8682
AttributesRewriter = rewriter,
87-
Attributes = attributes,
83+
Attributes = attributesPassParseResults.attributes,
8884
Comments = comments,
8985
Annotations = annotationListener.Annotations
9086
});
@@ -128,14 +124,12 @@ public void Start(CancellationToken token)
128124
}
129125
}
130126

131-
private ITokenStream RunAttributesPass(CancellationToken token, out IParseTree attributesTree,
132-
out IDictionary<Tuple<string, DeclarationType>, Attributes> attributes)
127+
private (IParseTree tree, ITokenStream tokenStream, IDictionary<Tuple<string, DeclarationType>, Attributes> attributes) RunAttributesPass(CancellationToken cancellationToken)
133128
{
134129
Logger.Trace($"ParseTaskID {_taskId} begins attributes pass.");
135-
ITokenStream attributesTokenStream;
136-
attributes = _attributeParser.Parse(_component, token, out attributesTokenStream, out attributesTree);
130+
var attributesParseResults = _attributeParser.Parse(_component, cancellationToken);
137131
Logger.Trace($"ParseTaskID {_taskId} finished attributes pass.");
138-
return attributesTokenStream;
132+
return attributesParseResults;
139133
}
140134

141135
private static string GetCode(ICodeModule module)
@@ -152,20 +146,20 @@ private static string GetCode(ICodeModule module)
152146
return code;
153147
}
154148

155-
private CommonTokenStream RewriteAndPreprocess(CancellationToken token)
149+
private CommonTokenStream RewriteAndPreprocess(CancellationToken cancellationToken)
156150
{
157-
var code = _rewriter == null ? string.Join(Environment.NewLine, GetCode(_component.CodeModule)) : _rewriter.GetText();
151+
var code = _rewriter?.GetText() ?? string.Join(Environment.NewLine, GetCode(_component.CodeModule));
158152
var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider();
159153
var tokens = tokenStreamProvider.Tokens(code);
160-
_preprocessor.PreprocessTokenStream(_component.Name, tokens, token);
154+
_preprocessor.PreprocessTokenStream(_component.Name, tokens, cancellationToken);
161155
return tokens;
162156
}
163157

164-
private IParseTree ParseInternal(string moduleName, CommonTokenStream tokenStream, IParseTreeListener[] listeners, out ITokenStream outStream)
158+
private (IParseTree tree, ITokenStream tokenStream) ParseInternal(string moduleName, CommonTokenStream tokenStream, IParseTreeListener[] listeners)
165159
{
166160
//var errorNotifier = new SyntaxErrorNotificationListener();
167161
//errorNotifier.OnSyntaxError += ParserSyntaxError;
168-
return _parser.Parse(moduleName, tokenStream, listeners, new ExceptionErrorListener(), out outStream);
162+
return _parser.Parse(moduleName, tokenStream, listeners, new ExceptionErrorListener());
169163
}
170164

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

Rubberduck.Parsing/VBA/IAttributeParser.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,6 @@ namespace Rubberduck.Parsing.VBA
1010
{
1111
public interface IAttributeParser
1212
{
13-
IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponent component, CancellationToken token, out ITokenStream stream, out IParseTree tree);
13+
(IParseTree tree, ITokenStream tokenStream, IDictionary<Tuple<string, DeclarationType>, Attributes> attributes) Parse(IVBComponent component, CancellationToken cancellationToken);
1414
}
1515
}

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 32 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
using System;
2+
using System.Collections.Concurrent;
23
using System.Collections.Generic;
34
using System.Threading;
45
using System.Threading.Tasks;
@@ -64,9 +65,8 @@ public ParseCoordinator(
6465
}
6566

6667
// Do not access this from anywhere but ReparseRequested.
67-
// ReparseRequested needs to have a reference to all the cancellation tokens,
68-
// but the cancelees need to use their own token.
69-
private readonly List<CancellationTokenSource> _cancellationTokens = new List<CancellationTokenSource> { new CancellationTokenSource() };
68+
// ReparseRequested needs to have a reference to the cancellation token.
69+
private CancellationTokenSource _currentCancellationTokenSource = new CancellationTokenSource();
7070

7171
private readonly object _cancellationSyncObject = new object();
7272
private readonly object _parsingRunSyncObject = new object();
@@ -77,9 +77,17 @@ private void ReparseRequested(object sender, EventArgs e)
7777
lock (_cancellationSyncObject)
7878
{
7979
Cancel();
80-
token = _cancellationTokens[0].Token;
80+
81+
if (_currentCancellationTokenSource == null)
82+
{
83+
Logger.Error("Tried to request a parse after the final cancellation.");
84+
return;
85+
}
86+
87+
token = _currentCancellationTokenSource.Token;
8188
}
8289

90+
8391
if (!_isTestScope)
8492
{
8593
Task.Run(() => ParseAll(sender, token), token);
@@ -92,15 +100,19 @@ private void ReparseRequested(object sender, EventArgs e)
92100

93101
private void Cancel(bool createNewTokenSource = true)
94102
{
95-
lock (_cancellationTokens[0])
103+
lock (_cancellationSyncObject)
96104
{
97-
_cancellationTokens[0].Cancel();
98-
_cancellationTokens[0].Dispose();
99-
if (createNewTokenSource)
105+
if (_currentCancellationTokenSource == null)
100106
{
101-
_cancellationTokens.Add(new CancellationTokenSource());
107+
Logger.Error("Tried to cancel a parse after the final cancellation.");
108+
return;
102109
}
103-
_cancellationTokens.RemoveAt(0);
110+
111+
var oldTokenSource = _currentCancellationTokenSource;
112+
_currentCancellationTokenSource = createNewTokenSource ? new CancellationTokenSource() : null;
113+
114+
oldTokenSource.Cancel();
115+
oldTokenSource.Dispose();
104116
}
105117
}
106118

@@ -114,18 +126,17 @@ public void Parse(CancellationTokenSource token)
114126
ParseInternal(token.Token);
115127
}
116128

117-
private void SetSavedCancellationTokenSource(CancellationTokenSource token)
129+
/// <summary>
130+
/// For the use of tests only
131+
/// </summary>
132+
///
133+
private void SetSavedCancellationTokenSource(CancellationTokenSource tokenSource)
118134
{
119-
if (_cancellationTokens.Any())
120-
{
121-
_cancellationTokens[0].Cancel();
122-
_cancellationTokens[0].Dispose();
123-
_cancellationTokens[0] = token;
124-
}
125-
else
126-
{
127-
_cancellationTokens.Add(token);
128-
}
135+
var oldTokenSource = _currentCancellationTokenSource;
136+
_currentCancellationTokenSource = tokenSource;
137+
138+
oldTokenSource?.Cancel();
139+
oldTokenSource?.Dispose();
129140
}
130141

131142
private void ParseInternal(CancellationToken token)

Rubberduck.Parsing/VBA/VBAModuleParser.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@ public sealed class VBAModuleParser
1111
{
1212
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
1313

14-
public IParseTree Parse(string moduleName, CommonTokenStream moduleTokens, IParseTreeListener[] listeners, BaseErrorListener errorListener, out ITokenStream outStream)
14+
public (IParseTree tree, ITokenStream tokenStream) Parse(string moduleName, CommonTokenStream moduleTokens, IParseTreeListener[] listeners, BaseErrorListener errorListener)
1515
{
1616
moduleTokens.Reset();
1717
var parser = new VBAParser(moduleTokens);
@@ -34,8 +34,7 @@ public IParseTree Parse(string moduleName, CommonTokenStream moduleTokens, IPars
3434
{
3535
ParseTreeWalker.Default.Walk(listener, tree);
3636
}
37-
outStream = moduleTokens;
38-
return tree;
37+
return (tree, moduleTokens);
3938
}
4039
}
4140
}

0 commit comments

Comments
 (0)