Skip to content

Commit f9412aa

Browse files
committed
Implemented the empty module inspection and fixed the setup in one test.
1 parent e29733a commit f9412aa

File tree

2 files changed

+87
-10
lines changed

2 files changed

+87
-10
lines changed
Lines changed: 86 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,26 +1,103 @@
1-
using System;
2-
using System.Collections.Generic;
1+
using System.Collections.Generic;
32
using System.Linq;
4-
using System.Text;
5-
using System.Threading.Tasks;
63
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing.Grammar;
76
using Rubberduck.Parsing.Inspections.Abstract;
87
using Rubberduck.Parsing.Inspections.Resources;
8+
using Rubberduck.Parsing.Symbols;
99
using Rubberduck.Parsing.VBA;
10+
using Rubberduck.VBEditor;
11+
using Rubberduck.VBEditor.SafeComWrappers;
1012

1113
namespace Rubberduck.Inspections.Concrete
1214
{
13-
class EmptyModuleInspection : InspectionBase
15+
16+
public sealed class EmptyModuleInspection : InspectionBase
1417
{
15-
public EmptyModuleInspection(RubberduckParserState state, CodeInspectionSeverity defaultSeverity = CodeInspectionSeverity.Hint)
16-
:base(state, defaultSeverity)
17-
{ }
18+
private EmptyModuleVisitor _emptyModuleVisitor;
19+
20+
public EmptyModuleInspection(RubberduckParserState state,
21+
CodeInspectionSeverity defaultSeverity = CodeInspectionSeverity.Hint)
22+
: base(state, defaultSeverity)
23+
{
24+
_emptyModuleVisitor = new EmptyModuleVisitor();
25+
}
1826

1927
public override CodeInspectionType InspectionType => CodeInspectionType.MaintainabilityAndReadabilityIssues;
2028

2129
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2230
{
23-
throw new NotImplementedException();
31+
var modulesToInspect = State.DeclarationFinder.AllModules
32+
.Where(qmn => qmn.ComponentType == ComponentType.ClassModule
33+
|| qmn.ComponentType == ComponentType.StandardModule).ToHashSet();
34+
35+
var treesToInspect = State.ParseTrees.Where(kvp => modulesToInspect.Contains(kvp.Key));
36+
37+
var emptyModules = treesToInspect
38+
.Where(kvp => _emptyModuleVisitor.Visit(kvp.Value))
39+
.Select(kvp => kvp.Key)
40+
.ToHashSet();
41+
42+
var emptyModuleDeclarations = State.DeclarationFinder.UserDeclarations(DeclarationType.Module)
43+
.Where(declaration => emptyModules.Contains(declaration.QualifiedName.QualifiedModuleName)
44+
&& !IsIgnoringInspectionResultFor(declaration, AnnotationName));
45+
46+
return emptyModuleDeclarations.Select(declaration =>
47+
new DeclarationInspectionResult(this, string.Format(InspectionsUI.EmptyModuleInspectionResultFormat, declaration.IdentifierName), declaration));
48+
}
49+
}
50+
51+
internal sealed class EmptyModuleVisitor : VBAParserBaseVisitor<bool>
52+
{
53+
//If not specified otherwise, any context makes a module non-empty.
54+
protected override bool DefaultResult => false;
55+
56+
protected override bool AggregateResult(bool aggregate, bool nextResult)
57+
{
58+
return aggregate && nextResult;
59+
}
60+
61+
//We bail out whenever we already know that the module is non-empty.
62+
protected override bool ShouldVisitNextChild(Antlr4.Runtime.Tree.IRuleNode node, bool currentResult)
63+
{
64+
return currentResult;
65+
}
66+
67+
68+
public override bool VisitStartRule(VBAParser.StartRuleContext context)
69+
{
70+
return Visit(context.module());
71+
}
72+
73+
public override bool VisitModule(VBAParser.ModuleContext context)
74+
{
75+
return context.moduleConfig() == null
76+
&& Visit(context.moduleBody())
77+
&& Visit(context.moduleDeclarations());
78+
}
79+
80+
public override bool VisitModuleBody(VBAParser.ModuleBodyContext context)
81+
{
82+
return !context.moduleBodyElement().Any();
83+
}
84+
85+
public override bool VisitModuleDeclarations(VBAParser.ModuleDeclarationsContext context)
86+
{
87+
return !context.moduleDeclarationsElement().Any()
88+
|| context.moduleDeclarationsElement().All(Visit);
89+
}
90+
91+
public override bool VisitModuleDeclarationsElement(VBAParser.ModuleDeclarationsElementContext context)
92+
{
93+
return context.variableStmt() == null
94+
&& context.constStmt() == null
95+
&& context.enumerationStmt() == null
96+
&& context.privateTypeDeclaration() == null
97+
&& context.publicTypeDeclaration() == null
98+
&& context.eventStmt() == null
99+
&& context.implementsStmt() == null
100+
&& context.declareStmt() == null;
24101
}
25102
}
26103
}

RubberduckTests/Inspections/EmptyModuleInspectionTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -288,7 +288,7 @@ public void EmptyDocumentModule_DoesNotReturnResult()
288288
{
289289
const string inputCode = "";
290290

291-
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
291+
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.Document, out _);
292292
using (var state = MockParser.CreateAndParse(vbe.Object))
293293
{
294294

0 commit comments

Comments
 (0)