Skip to content

Commit a6ea3c8

Browse files
committed
Merge branch 'next' into BringUserFormExportEncodingInLineWithTheVBE
2 parents 3e6b9ff + c0441e8 commit a6ea3c8

18 files changed

+553
-59
lines changed

RetailCoder.VBE/Navigation/CodeExplorer/CodeExplorerViewModel.cs

Lines changed: 14 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -374,7 +374,7 @@ private void ParserState_ModuleStateChanged(object sender, Parsing.ParseProgress
374374
return;
375375
}
376376

377-
var components = e.Component.Collection;
377+
var components = e.Module.Component.Collection;
378378
var componentProject = components.Parent;
379379
{
380380
var projectNode = Projects.OfType<CodeExplorerProjectViewModel>()
@@ -385,7 +385,7 @@ private void ParserState_ModuleStateChanged(object sender, Parsing.ParseProgress
385385
return;
386386
}
387387

388-
SetErrorState(projectNode, e.Component);
388+
SetErrorState(projectNode, e.Module);
389389

390390
if (_errorStateSet) { return; }
391391

@@ -401,7 +401,7 @@ private void ParserState_ModuleStateChanged(object sender, Parsing.ParseProgress
401401
projectNode.AddChild(folderNode);
402402
}
403403

404-
var declaration = CreateDeclaration(e.Component);
404+
var declaration = CreateDeclaration(e.Module);
405405
var newNode = new CodeExplorerComponentViewModel(folderNode, declaration, new List<Declaration>())
406406
{
407407
IsErrorState = true
@@ -415,22 +415,21 @@ private void ParserState_ModuleStateChanged(object sender, Parsing.ParseProgress
415415
}
416416
}
417417

418-
private Declaration CreateDeclaration(IVBComponent component)
418+
private Declaration CreateDeclaration(QualifiedModuleName module)
419419
{
420420
var projectDeclaration =
421-
_state.AllUserDeclarations.FirstOrDefault(item =>
422-
item.DeclarationType == DeclarationType.Project &&
423-
item.Project.VBComponents.Contains(component));
421+
_state.DeclarationFinder.UserDeclarations(DeclarationType.Project)
422+
.FirstOrDefault(item => item.Project.VBComponents.Contains(module.Component));
424423

425-
if (component.Type == ComponentType.StandardModule)
424+
if (module.ComponentType == ComponentType.StandardModule)
426425
{
427426
return new ProceduralModuleDeclaration(
428-
new QualifiedMemberName(new QualifiedModuleName(component), component.Name), projectDeclaration,
429-
component.Name, true, new List<IAnnotation>(), null);
427+
new QualifiedMemberName(module, module.ComponentName), projectDeclaration,
428+
module.ComponentName, true, new List<IAnnotation>(), null);
430429
}
431430

432-
return new ClassModuleDeclaration(new QualifiedMemberName(new QualifiedModuleName(component), component.Name),
433-
projectDeclaration, component.Name, true, new List<IAnnotation>(), null);
431+
return new ClassModuleDeclaration(new QualifiedMemberName(module, module.ComponentName),
432+
projectDeclaration, module.ComponentName, true, new List<IAnnotation>(), null);
434433
}
435434

436435
private void ReorderChildNodes(IEnumerable<CodeExplorerItemViewModel> nodes)
@@ -443,15 +442,15 @@ private void ReorderChildNodes(IEnumerable<CodeExplorerItemViewModel> nodes)
443442
}
444443

445444
private bool _errorStateSet;
446-
private void SetErrorState(CodeExplorerItemViewModel itemNode, IVBComponent component)
445+
private void SetErrorState(CodeExplorerItemViewModel itemNode, QualifiedModuleName module)
447446
{
448447
_errorStateSet = false;
449448

450449
foreach (var node in itemNode.Items)
451450
{
452451
if (node is CodeExplorerCustomFolderViewModel)
453452
{
454-
SetErrorState(node, component);
453+
SetErrorState(node, module);
455454
}
456455

457456
if (_errorStateSet)
@@ -460,7 +459,7 @@ private void SetErrorState(CodeExplorerItemViewModel itemNode, IVBComponent comp
460459
}
461460

462461
var componentNode = node as CodeExplorerComponentViewModel;
463-
if (componentNode?.GetSelectedDeclaration().QualifiedName.QualifiedModuleName.Component.Equals(component) == true)
462+
if (componentNode?.GetSelectedDeclaration().QualifiedName.QualifiedModuleName.Equals(module) == true)
464463
{
465464
componentNode.IsErrorState = true;
466465
_errorStateSet = true;

RetailCoder.VBE/UI/Command/AddTestMethodCommand.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -82,7 +82,7 @@ protected override void OnExecute(object parameter)
8282
module.InsertLines(module.CountOfLines, body);
8383
}
8484

85-
_state.OnParseRequested(this, _vbe.SelectedVBComponent);
85+
_state.OnParseRequested(this);
8686
}
8787

8888
private string GetNextTestMethodName(IVBComponent component)

RetailCoder.VBE/UI/Command/AddTestMethodExpectedErrorCommand.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -101,7 +101,7 @@ protected override void OnExecute(object parameter)
101101
module.InsertLines(module.CountOfLines, body);
102102
}
103103

104-
_state.OnParseRequested(this, _vbe.SelectedVBComponent);
104+
_state.OnParseRequested(this);
105105
}
106106

107107
private string GetNextTestMethodName(IVBComponent component)

RetailCoder.VBE/UI/Command/AddTestModuleCommand.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -212,7 +212,7 @@ protected override void OnExecute(object parameter)
212212
}
213213

214214
component.Activate();
215-
_state.OnParseRequested(this, component);
215+
_state.OnParseRequested(this);
216216
}
217217

218218
private string GetNextTestModuleName(IVBProject project)

RetailCoder.VBE/UI/Command/IndentCurrentModuleCommand.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,7 @@ protected override void OnExecute(object parameter)
3333
_indenter.IndentCurrentModule();
3434
if (_state.Status >= ParserState.Ready || _state.Status == ParserState.Pending)
3535
{
36-
_state.OnParseRequested(this, _vbe.ActiveCodePane.CodeModule.Parent);
36+
_state.OnParseRequested(this);
3737
}
3838
}
3939
}

RetailCoder.VBE/UI/Command/IndentCurrentProcedureCommand.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ protected override void OnExecute(object parameter)
3434
_indenter.IndentCurrentProcedure();
3535
if (_state.Status >= ParserState.Ready || _state.Status == ParserState.Pending)
3636
{
37-
_state.OnParseRequested(this, _vbe.ActiveCodePane.CodeModule.Parent);
37+
_state.OnParseRequested(this);
3838
}
3939
}
4040
}

RetailCoder.VBE/UI/Command/Refactorings/RefactorExtractMethodCommand.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -105,7 +105,7 @@ protected override void OnExecute(object parameter)
105105

106106
var extraction = new ExtractMethodExtraction();
107107
// bug: access to disposed closure - todo: make ExtractMethodRefactoring request reparse like everyone else.
108-
Action<object> parseRequest = obj => _state.OnParseRequested(obj, component);
108+
Action<object> parseRequest = obj => _state.OnParseRequested(obj);
109109

110110
var refactoring = new ExtractMethodRefactoring(module, parseRequest, createMethodModel, extraction);
111111
refactoring.InvalidSelection += HandleInvalidSelection;

RetailCoder.VBE/UI/Command/ShowParserErrorsCommand.cs

Lines changed: 11 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,6 @@
99
using Rubberduck.UI.Command.MenuItems;
1010
using Rubberduck.UI.Controls;
1111
using Rubberduck.VBEditor;
12-
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1312

1413
namespace Rubberduck.UI.Command
1514
{
@@ -105,24 +104,18 @@ private SearchResultsViewModel CreateViewModel()
105104
return viewModel;
106105
}
107106

108-
private Declaration FindModuleDeclaration(IVBComponent component)
107+
private Declaration FindModuleDeclaration(QualifiedModuleName module)
109108
{
110-
var components = component.Collection;
111-
var refProject = components.Parent;
112-
{
113-
var projectId = refProject.HelpFile;
114-
var project = _state.AllUserDeclarations.SingleOrDefault(item =>
115-
item.DeclarationType == DeclarationType.Project && item.ProjectId == projectId);
116-
117-
var result = _state.AllUserDeclarations.SingleOrDefault(item =>
118-
item.ProjectId == component.Collection.Parent.HelpFile
119-
&& item.QualifiedName.QualifiedModuleName.ComponentName == component.Name
120-
&& (item.DeclarationType == DeclarationType.ClassModule || item.DeclarationType == DeclarationType.ProceduralModule));
121-
122-
// FIXME dirty hack for project.Scope in case project is null. Clean up!
123-
var declaration = new Declaration(new QualifiedMemberName(new QualifiedModuleName(component), component.Name), project, project?.Scope, component.Name, null, false, false, Accessibility.Global, DeclarationType.ProceduralModule, false, null, true);
124-
return result ?? declaration; // module isn't in parser state - give it a dummy declaration, just so the ViewModel has something to chew on
125-
}
109+
var projectId = module.ProjectId;
110+
var project = _state.DeclarationFinder.UserDeclarations(DeclarationType.Project)
111+
.SingleOrDefault(item => item.ProjectId == projectId);
112+
113+
var result = _state.DeclarationFinder.UserDeclarations(DeclarationType.Module)
114+
.SingleOrDefault(item => item.QualifiedName.QualifiedModuleName.Equals(module));
115+
116+
// FIXME dirty hack for project.Scope in case project is null. Clean up!
117+
var declaration = new Declaration(new QualifiedMemberName(module, module.ComponentName), project, project?.Scope, module.ComponentName, null, false, false, Accessibility.Global, DeclarationType.ProceduralModule, false, null, true);
118+
return result ?? declaration; // module isn't in parser state - give it a dummy declaration, just so the ViewModel has something to chew on
126119
}
127120

128121
public void Dispose()
Lines changed: 103 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,103 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.Parsing.Inspections.Abstract;
7+
using Rubberduck.Parsing.Inspections.Resources;
8+
using Rubberduck.Parsing.Symbols;
9+
using Rubberduck.Parsing.VBA;
10+
using Rubberduck.VBEditor;
11+
using Rubberduck.VBEditor.SafeComWrappers;
12+
13+
namespace Rubberduck.Inspections.Concrete
14+
{
15+
16+
public sealed class EmptyModuleInspection : InspectionBase
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+
}
26+
27+
public override CodeInspectionType InspectionType => CodeInspectionType.MaintainabilityAndReadabilityIssues;
28+
29+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
30+
{
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;
101+
}
102+
}
103+
}

Rubberduck.Inspections/Rubberduck.Inspections.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -62,6 +62,7 @@
6262
<Compile Include="Abstract\ParseTreeInspectionBase.cs" />
6363
<Compile Include="Concrete\ApplicationWorksheetFunctionInspection.cs" />
6464
<Compile Include="Concrete\AssignedByValParameterInspection.cs" />
65+
<Compile Include="Concrete\EmptyModuleInspection.cs" />
6566
<Compile Include="Concrete\EmptyBlockInspectionListenerBase.cs" />
6667
<Compile Include="Concrete\EmptyCaseBlockInspection.cs" />
6768
<Compile Include="Concrete\EmptyDoWhileBlockInspection.cs" />

0 commit comments

Comments
 (0)