Skip to content

Commit 19594ae

Browse files
committed
Extracted the Inspections out of RubberduckParser into Inspector, adjusted inspection return type to IEnumerable, see #1441
1 parent 45208f1 commit 19594ae

File tree

11 files changed

+159
-95
lines changed

11 files changed

+159
-95
lines changed

RetailCoder.VBE/Inspections/EmptyStringLiteralInspection.cs

Lines changed: 24 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,10 +3,11 @@
33
using Antlr4.Runtime;
44
using Rubberduck.Parsing;
55
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.Parsing.Grammar;
67

78
namespace Rubberduck.Inspections
89
{
9-
public sealed class EmptyStringLiteralInspection : InspectionBase
10+
public sealed class EmptyStringLiteralInspection : InspectionBase, IParseTreeInspection
1011
{
1112
public EmptyStringLiteralInspection(RubberduckParserState state)
1213
: base(state)
@@ -17,11 +18,32 @@ public EmptyStringLiteralInspection(RubberduckParserState state)
1718
public override string Description { get { return InspectionsUI.EmptyStringLiteralInspection; } }
1819
public override CodeInspectionType InspectionType { get { return CodeInspectionType.LanguageOpportunities; } }
1920

21+
public ParseTreeResults ParseTreeResults { get; set; }
22+
2023
public override IEnumerable<InspectionResultBase> GetInspectionResults()
2124
{
22-
return State.EmptyStringLiterals.Select(
25+
if (ParseTreeResults == null)
26+
{
27+
return new InspectionResultBase[] { };
28+
}
29+
return ParseTreeResults.EmptyStringLiterals.Select(
2330
context => new EmptyStringLiteralInspectionResult(this,
2431
new QualifiedContext<ParserRuleContext>(context.ModuleName, context.Context)));
2532
}
33+
34+
public class EmptyStringLiteralListener : VBAParserBaseListener
35+
{
36+
private readonly IList<VBAParser.LiteralContext> _contexts = new List<VBAParser.LiteralContext>();
37+
public IEnumerable<VBAParser.LiteralContext> Contexts { get { return _contexts; } }
38+
39+
public override void ExitLiteral(VBAParser.LiteralContext context)
40+
{
41+
var literal = context.STRINGLITERAL();
42+
if (literal != null && literal.GetText() == "\"\"")
43+
{
44+
_contexts.Add(context);
45+
}
46+
}
47+
}
2648
}
2749
}

RetailCoder.VBE/Inspections/IInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,5 @@ public interface IInspection : IInspectionModel, IComparable<IInspection>, IComp
1818
/// Gets a string that contains additional/meta information about an inspection.
1919
/// </summary>
2020
string Meta { get; }
21-
2221
}
2322
}

RetailCoder.VBE/Inspections/IInspector.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -8,15 +8,15 @@ namespace Rubberduck.Inspections
88
{
99
public interface IInspector
1010
{
11-
Task<IList<ICodeInspectionResult>> FindIssuesAsync(RubberduckParserState state, CancellationToken token);
11+
Task<IEnumerable<ICodeInspectionResult>> FindIssuesAsync(RubberduckParserState state, CancellationToken token);
1212
}
1313

1414
public class InspectorIssuesFoundEventArg : EventArgs
1515
{
16-
private readonly IList<InspectionResultBase> _issues;
17-
public IList<InspectionResultBase> Issues { get { return _issues; } }
16+
private readonly IEnumerable<InspectionResultBase> _issues;
17+
public IEnumerable<InspectionResultBase> Issues { get { return _issues; } }
1818

19-
public InspectorIssuesFoundEventArg(IList<InspectionResultBase> issues)
19+
public InspectorIssuesFoundEventArg(IEnumerable<InspectionResultBase> issues)
2020
{
2121
_issues = issues;
2222
}
Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
using Rubberduck.Parsing;
2+
using System.Collections.Generic;
3+
4+
namespace Rubberduck.Inspections
5+
{
6+
internal interface IParseTreeInspection : IInspection
7+
{
8+
ParseTreeResults ParseTreeResults { get; set; }
9+
}
10+
11+
public sealed class ParseTreeResults
12+
{
13+
public IList<QualifiedContext> ObsoleteCallContexts;
14+
public IList<QualifiedContext> ObsoleteLetContexts;
15+
public IList<QualifiedContext> ArgListsWithOneByRefParam;
16+
public IList<QualifiedContext> EmptyStringLiterals;
17+
}
18+
}

RetailCoder.VBE/Inspections/Inspector.cs

Lines changed: 44 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,8 @@
77
using Rubberduck.Parsing.VBA;
88
using Rubberduck.Settings;
99
using Rubberduck.UI;
10+
using Antlr4.Runtime.Tree;
11+
using Rubberduck.Parsing;
1012

1113
namespace Rubberduck.Inspections
1214
{
@@ -46,7 +48,7 @@ private void UpdateInspectionSeverity()
4648
}
4749
}
4850

49-
public async Task<IList<ICodeInspectionResult>> FindIssuesAsync(RubberduckParserState state, CancellationToken token)
51+
public async Task<IEnumerable<ICodeInspectionResult>> FindIssuesAsync(RubberduckParserState state, CancellationToken token)
5052
{
5153
if (state == null || !state.AllUserDeclarations.Any())
5254
{
@@ -61,13 +63,20 @@ public async Task<IList<ICodeInspectionResult>> FindIssuesAsync(RubberduckParser
6163

6264
var allIssues = new ConcurrentBag<ICodeInspectionResult>();
6365

66+
// Prepare ParseTreeWalker based inspections
67+
var parseTreeWalkResults = GetParseTreeResults(state);
68+
foreach (var parseTreeInspection in _inspections.Where(inspection => inspection.Severity != CodeInspectionSeverity.DoNotShow && inspection is IParseTreeInspection))
69+
{
70+
(parseTreeInspection as IParseTreeInspection).ParseTreeResults = parseTreeWalkResults;
71+
}
72+
6473
var inspections = _inspections.Where(inspection => inspection.Severity != CodeInspectionSeverity.DoNotShow)
6574
.Select(inspection =>
6675
new Task(() =>
6776
{
6877
token.ThrowIfCancellationRequested();
6978
var inspectionResults = inspection.GetInspectionResults();
70-
var results = inspectionResults as IList<InspectionResultBase> ?? inspectionResults.ToList();
79+
var results = inspectionResults as IEnumerable<InspectionResultBase> ?? inspectionResults;
7180

7281
if (results.Any())
7382
{
@@ -88,7 +97,39 @@ public async Task<IList<ICodeInspectionResult>> FindIssuesAsync(RubberduckParser
8897
Task.WaitAll(inspections);
8998
state.OnStatusMessageUpdate(RubberduckUI.ResourceManager.GetString("ParserState_" + state.Status)); // should be "Ready"
9099

91-
return allIssues.ToList();
100+
return allIssues;
101+
}
102+
103+
private ParseTreeResults GetParseTreeResults(RubberduckParserState state)
104+
{
105+
var result = new ParseTreeResults();
106+
107+
foreach (var componentTreePair in state.ParseTrees)
108+
{
109+
/*
110+
Need to reinitialize these for each and every ParseTree we process, since the results are aggregated in the instances themselves
111+
before moving them into the ParseTreeResults after qualifying them
112+
*/
113+
var obsoleteCallStatementListener = new ObsoleteCallStatementInspection.ObsoleteCallStatementListener();
114+
var obsoleteLetStatementListener = new ObsoleteLetStatementInspection.ObsoleteLetStatementListener();
115+
var emptyStringLiteralListener = new EmptyStringLiteralInspection.EmptyStringLiteralListener();
116+
var argListWithOneByRefParamListener = new ProcedureCanBeWrittenAsFunctionInspection.ArgListWithOneByRefParamListener();
117+
118+
var combinedListener = new CombinedParseTreeListener(new IParseTreeListener[]{
119+
obsoleteCallStatementListener,
120+
obsoleteLetStatementListener,
121+
emptyStringLiteralListener,
122+
argListWithOneByRefParamListener,
123+
});
124+
125+
ParseTreeWalker.Default.Walk(combinedListener, componentTreePair.Value);
126+
127+
result.ArgListsWithOneByRefParam.Concat(argListWithOneByRefParamListener.Contexts.Select(context => new QualifiedContext(componentTreePair.Key, context)));
128+
result.EmptyStringLiterals.Concat(emptyStringLiteralListener.Contexts.Select(context => new QualifiedContext(componentTreePair.Key, context)));
129+
result.ObsoleteLetContexts.Concat(obsoleteLetStatementListener.Contexts.Select(context => new QualifiedContext(componentTreePair.Key, context)));
130+
result.ObsoleteCallContexts.Concat(obsoleteCallStatementListener.Contexts.Select(context => new QualifiedContext(componentTreePair.Key, context)));
131+
}
132+
return result;
92133
}
93134

94135
public void Dispose()

RetailCoder.VBE/Inspections/ObsoleteCallStatementInspection.cs

Lines changed: 20 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@
66

77
namespace Rubberduck.Inspections
88
{
9-
public sealed class ObsoleteCallStatementInspection : InspectionBase
9+
public sealed class ObsoleteCallStatementInspection : InspectionBase, IParseTreeInspection
1010
{
1111
public ObsoleteCallStatementInspection(RubberduckParserState state)
1212
: base(state, CodeInspectionSeverity.Suggestion)
@@ -16,12 +16,30 @@ public ObsoleteCallStatementInspection(RubberduckParserState state)
1616
public override string Meta { get { return InspectionsUI.ObsoleteCallStatementInspectionMeta; } }
1717
public override string Description { get { return InspectionsUI.ObsoleteCallStatementInspectionResultFormat; } }
1818
public override CodeInspectionType InspectionType { get { return CodeInspectionType.LanguageOpportunities; } }
19+
public ParseTreeResults ParseTreeResults { get; set; }
1920

2021
public override IEnumerable<InspectionResultBase> GetInspectionResults()
2122
{
22-
return State.ObsoleteCallContexts.Select(context =>
23+
if (ParseTreeResults == null)
24+
{
25+
return new InspectionResultBase[] { };
26+
}
27+
28+
return ParseTreeResults.ObsoleteCallContexts.Select(context =>
2329
new ObsoleteCallStatementUsageInspectionResult(this,
2430
new QualifiedContext<VBAParser.ExplicitCallStmtContext>(context.ModuleName, context.Context as VBAParser.ExplicitCallStmtContext)));
2531
}
32+
33+
public class ObsoleteCallStatementListener : VBAParserBaseListener
34+
{
35+
private readonly IList<VBAParser.ExplicitCallStmtContext> _contexts = new List<VBAParser.ExplicitCallStmtContext>();
36+
public IEnumerable<VBAParser.ExplicitCallStmtContext> Contexts { get { return _contexts; } }
37+
38+
public override void ExitExplicitCallStmt(VBAParser.ExplicitCallStmtContext context)
39+
{
40+
_contexts.Add(context);
41+
}
42+
}
43+
2644
}
2745
}

RetailCoder.VBE/Inspections/ObsoleteLetStatementInspection.cs

Lines changed: 22 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,10 +3,11 @@
33
using Antlr4.Runtime;
44
using Rubberduck.Parsing;
55
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.Parsing.Grammar;
67

78
namespace Rubberduck.Inspections
89
{
9-
public sealed class ObsoleteLetStatementInspection : InspectionBase
10+
public sealed class ObsoleteLetStatementInspection : InspectionBase, IParseTreeInspection
1011
{
1112
public ObsoleteLetStatementInspection(RubberduckParserState state)
1213
: base(state, CodeInspectionSeverity.Suggestion)
@@ -16,11 +17,30 @@ public ObsoleteLetStatementInspection(RubberduckParserState state)
1617
public override string Meta { get { return InspectionsUI.ObsoleteLetStatementInspectionMeta; } }
1718
public override string Description { get { return InspectionsUI.ObsoleteLetStatementInspectionResultFormat; } }
1819
public override CodeInspectionType InspectionType { get { return CodeInspectionType.LanguageOpportunities; } }
20+
public ParseTreeResults ParseTreeResults { get; set; }
1921

2022
public override IEnumerable<InspectionResultBase> GetInspectionResults()
2123
{
22-
return State.ObsoleteLetContexts.Select(context =>
24+
if (ParseTreeResults == null)
25+
{
26+
return new InspectionResultBase[] { };
27+
}
28+
return ParseTreeResults.ObsoleteLetContexts.Select(context =>
2329
new ObsoleteLetStatementUsageInspectionResult(this, new QualifiedContext<ParserRuleContext>(context.ModuleName, context.Context)));
2430
}
31+
32+
public class ObsoleteLetStatementListener : VBAParserBaseListener
33+
{
34+
private readonly IList<VBAParser.LetStmtContext> _contexts = new List<VBAParser.LetStmtContext>();
35+
public IEnumerable<VBAParser.LetStmtContext> Contexts { get { return _contexts; } }
36+
37+
public override void ExitLetStmt(VBAParser.LetStmtContext context)
38+
{
39+
if (context.LET() != null)
40+
{
41+
_contexts.Add(context);
42+
}
43+
}
44+
}
2545
}
2646
}

RetailCoder.VBE/Inspections/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 25 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,10 +5,11 @@
55
using Rubberduck.Parsing.Grammar;
66
using Rubberduck.Parsing.Symbols;
77
using Rubberduck.Parsing.VBA;
8+
using System.Diagnostics;
89

910
namespace Rubberduck.Inspections
1011
{
11-
public sealed class ProcedureCanBeWrittenAsFunctionInspection : InspectionBase
12+
public sealed class ProcedureCanBeWrittenAsFunctionInspection : InspectionBase, IParseTreeInspection
1213
{
1314
public ProcedureCanBeWrittenAsFunctionInspection(RubberduckParserState state)
1415
: base(state, CodeInspectionSeverity.Suggestion)
@@ -19,9 +20,16 @@ public ProcedureCanBeWrittenAsFunctionInspection(RubberduckParserState state)
1920
public override string Description { get { return InspectionsUI.ProcedureCanBeWrittenAsFunctionInspectionResultFormat; } }
2021
public override CodeInspectionType InspectionType { get { return CodeInspectionType.LanguageOpportunities; } }
2122

23+
public ParseTreeResults ParseTreeResults { get; set; }
24+
2225
public override IEnumerable<InspectionResultBase> GetInspectionResults()
2326
{
24-
var subStmts = State.ArgListsWithOneByRefParam
27+
if (ParseTreeResults == null)
28+
{
29+
Debug.WriteLine("Aborting GetInspectionResults because ParseTree results were not passed");
30+
return new InspectionResultBase[] { };
31+
}
32+
var subStmts = ParseTreeResults.ArgListsWithOneByRefParam
2533
.Where(context => context.Context.Parent is VBAParser.SubStmtContext)
2634
.Select(context => (VBAParser.SubStmtContext)context.Context.Parent)
2735
.ToList();
@@ -63,7 +71,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
6371
.All(withEvents => UserDeclarations.FindEventProcedures(withEvents) == null);
6472
});
6573

66-
return State.ArgListsWithOneByRefParam
74+
return ParseTreeResults.ArgListsWithOneByRefParam
6775
.Where(context => context.Context.Parent is VBAParser.SubStmtContext &&
6876
subStmtsNotImplementingInterfaces.Contains(context.Context.Parent) &&
6977
subStmtsNotImplementingEvents.Contains(context.Context.Parent))
@@ -74,5 +82,19 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
7482
new QualifiedContext<VBAParser.SubStmtContext>(context.ModuleName,
7583
context.Context.Parent as VBAParser.SubStmtContext)));
7684
}
85+
86+
public class ArgListWithOneByRefParamListener : VBAParserBaseListener
87+
{
88+
private readonly IList<VBAParser.ArgListContext> _contexts = new List<VBAParser.ArgListContext>();
89+
public IEnumerable<VBAParser.ArgListContext> Contexts { get { return _contexts; } }
90+
91+
public override void ExitArgList(VBAParser.ArgListContext context)
92+
{
93+
if (context.arg() != null && context.arg().Count(a => a.BYREF() != null || (a.BYREF() == null && a.BYVAL() == null)) == 1)
94+
{
95+
_contexts.Add(context);
96+
}
97+
}
98+
}
7799
}
78100
}

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -361,6 +361,7 @@
361361
<AutoGen>True</AutoGen>
362362
<DesignTime>True</DesignTime>
363363
</Compile>
364+
<Compile Include="Inspections\IParseTreeInspection.cs" />
364365
<Compile Include="Inspections\MakeSingleLineParameterQuickFix.cs" />
365366
<Compile Include="Inspections\ObjectVariableNotSetInspection.cs" />
366367
<Compile Include="Inspections\RemoveExplicitCallStatmentQuickFix.cs" />

RetailCoder.VBE/UI/CodeInspections/InspectionResultsViewModel.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -155,6 +155,7 @@ private async void ExecuteRefreshCommandAsync(object parameter)
155155
{
156156
return;
157157
}
158+
await Task.Yield();
158159

159160
IsBusy = true;
160161

0 commit comments

Comments
 (0)