Skip to content

Commit 7123cac

Browse files
committed
Merge pull request #1720 from Hosch250/InspectionBugs
Inspection bugs
2 parents aeb361d + f32c499 commit 7123cac

11 files changed

+188
-9
lines changed

RetailCoder.VBE/Common/DeclarationExtensions.cs

Lines changed: 31 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -222,12 +222,40 @@ public static IEnumerable<Declaration> FindEventHandlers(this IEnumerable<Declar
222222

223223
public static IEnumerable<Declaration> FindBuiltInEventHandlers(this IEnumerable<Declaration> declarations)
224224
{
225-
var handlerNames = declarations.Where(declaration => declaration.IsBuiltIn && declaration.DeclarationType == DeclarationType.Event)
225+
var declarationList = declarations.ToList();
226+
227+
var handlerNames = declarationList.Where(declaration => declaration.IsBuiltIn && declaration.DeclarationType == DeclarationType.Event)
226228
.Select(e => e.ParentDeclaration.IdentifierName + "_" + e.IdentifierName);
227229

228-
return declarations.Where(declaration => !declaration.IsBuiltIn
230+
// class module built-in events
231+
var classModuleHandlers = declarationList.Where(item =>
232+
item.DeclarationType == DeclarationType.Procedure &&
233+
item.ParentDeclaration.DeclarationType == DeclarationType.ClassModule &&
234+
(item.IdentifierName == "Class_Initialize" || item.IdentifierName == "Class_Terminate"));
235+
236+
// user form built-in events
237+
var userFormHandlers = declarationList.Where(item =>
238+
item.DeclarationType == DeclarationType.Procedure &&
239+
item.ParentDeclaration.DeclarationType == DeclarationType.ClassModule &&
240+
item.QualifiedName.QualifiedModuleName.Component.Type == vbext_ComponentType.vbext_ct_MSForm &&
241+
new[]
242+
{
243+
"UserForm_Activate", "UserForm_AddControl", "UserForm_BeforeDragOver", "UserForm_BeforeDropOrPaste",
244+
"UserForm_Click", "UserForm_DblClick", "UserForm_Deactivate", "UserForm_Error",
245+
"UserForm_Initialize", "UserForm_KeyDown", "UserForm_KeyPress", "UserForm_KeyUp", "UserForm_Layout",
246+
"UserForm_MouseDown", "UserForm_MouseMove", "UserForm_MouseUp", "UserForm_QueryClose",
247+
"UserForm_RemoveControl", "UserForm_Resize", "UserForm_Scroll", "UserForm_Terminate",
248+
"UserForm_Zoom"
249+
}.Contains(item.IdentifierName));
250+
251+
var handlers = declarationList.Where(declaration => !declaration.IsBuiltIn
229252
&& declaration.DeclarationType == DeclarationType.Procedure
230-
&& handlerNames.Contains(declaration.IdentifierName));
253+
&& handlerNames.Contains(declaration.IdentifierName)).ToList();
254+
255+
handlers.AddRange(classModuleHandlers);
256+
handlers.AddRange(userFormHandlers);
257+
258+
return handlers;
231259
}
232260

233261
/// <summary>

RetailCoder.VBE/Inspections/ImplicitByRefParameterInspection.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3030
// ParamArray parameters do not allow an explicit "ByRef" parameter mechanism.
3131
&& !((ParameterDeclaration)item).IsParamArray
3232
&& !interfaceMembers.Select(m => m.Scope).Contains(item.ParentScope)
33+
&& !UserDeclarations.FindBuiltInEventHandlers().Contains(item.ParentDeclaration)
3334
let arg = item.Context as VBAParser.ArgContext
3435
where arg != null && arg.BYREF() == null && arg.BYVAL() == null
3536
select new QualifiedContext<VBAParser.ArgContext>(item.QualifiedName, arg))

RetailCoder.VBE/Inspections/ParameterCanBeByValInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
4949

5050
var eventScopes = declarations.Where(item =>
5151
!item.IsBuiltIn && item.DeclarationType == DeclarationType.Event)
52-
.Select(e => e.Scope);
52+
.Select(e => e.Scope).Concat(declarations.FindBuiltInEventHandlers().Select(e => e.Scope));
5353

5454
var declareScopes = declarations.Where(item =>
5555
item.DeclarationType == DeclarationType.LibraryFunction

RetailCoder.VBE/Inspections/ParameterNotUsedInspection.cs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,13 +2,11 @@
22
using System.Linq;
33
using Microsoft.Vbe.Interop;
44
using Rubberduck.Common;
5-
using Rubberduck.Parsing.Grammar;
65
using Rubberduck.Parsing.Symbols;
76
using Rubberduck.Parsing.VBA;
87
using Rubberduck.Refactorings.RemoveParameters;
98
using Rubberduck.UI;
109
using Rubberduck.UI.Refactorings;
11-
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodePane;
1210

1311
namespace Rubberduck.Inspections
1412
{
@@ -38,8 +36,9 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3836
var builtInHandlers = declarations.FindBuiltInEventHandlers();
3937

4038
var parameters = declarations.Where(parameter => parameter.DeclarationType == DeclarationType.Parameter
41-
&& !(parameter.Context.Parent.Parent is VBAParser.EventStmtContext)
42-
&& !(parameter.Context.Parent.Parent is VBAParser.DeclareStmtContext));
39+
&& parameter.ParentDeclaration.DeclarationType != DeclarationType.Event
40+
&& parameter.ParentDeclaration.DeclarationType != DeclarationType.LibraryFunction
41+
&& parameter.ParentDeclaration.DeclarationType != DeclarationType.LibraryProcedure);
4342

4443
var unused = parameters.Where(parameter => !parameter.References.Any()).ToList();
4544
var quickFixRefactoring =

RetailCoder.VBE/Inspections/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -71,7 +71,8 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
7171
if (declaration == null) { return false; } // rather be safe than sorry
7272

7373
return UserDeclarations.Where(item => item.IsWithEvents)
74-
.All(withEvents => UserDeclarations.FindEventProcedures(withEvents) == null);
74+
.All(withEvents => UserDeclarations.FindEventProcedures(withEvents) == null) &&
75+
!UserDeclarations.FindBuiltInEventHandlers().Contains(declaration);
7576
});
7677

7778
return ParseTreeResults.ArgListsWithOneByRefParam

RetailCoder.VBE/Inspections/ProcedureNotUsedInspection.cs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,8 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
4242
handlers.AddRange(forms.SelectMany(form => declarations.FindFormEventHandlers(form)));
4343
}
4444

45+
handlers.AddRange(declarations.FindBuiltInEventHandlers());
46+
4547
var items = declarations
4648
.Where(item => !IsIgnoredDeclaration(declarations, item, handlers, classes, modules)
4749
&& !item.IsInspectionDisabled(AnnotationName)).ToList();

RubberduckTests/Inspections/ImplicitByRefParameterInspectionTests.cs

Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -173,6 +173,36 @@ Sub IClass1_Foo(arg1 As Integer)
173173
Assert.AreEqual(1, inspectionResults.Count());
174174
}
175175

176+
[TestMethod]
177+
[TestCategory("Inspections")]
178+
public void ImplicitByRefParameter_DoesNotReturnResult_BuiltInEvent()
179+
{
180+
//Input
181+
const string inputCode =
182+
@"Private Sub UserForm_Zoom(Percent As Integer)
183+
184+
End Sub";
185+
186+
//Arrange
187+
var builder = new MockVbeBuilder();
188+
var project = builder.ProjectBuilder("TestProject1", vbext_ProjectProtection.vbext_pp_none)
189+
.AddComponent("Class1", vbext_ComponentType.vbext_ct_MSForm, inputCode)
190+
.Build();
191+
var vbe = builder.AddProject(project).Build();
192+
193+
var mockHost = new Mock<IHostApplication>();
194+
mockHost.SetupAllProperties();
195+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState());
196+
197+
parser.Parse();
198+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
199+
200+
var inspection = new ImplicitByRefParameterInspection(parser.State);
201+
var inspectionResults = inspection.GetInspectionResults();
202+
203+
Assert.AreEqual(0, inspectionResults.Count());
204+
}
205+
176206
[TestMethod]
177207
[TestCategory("Inspections")]
178208
public void ImplicitByRefParameter_QuickFixWorks_PassByRef()

RubberduckTests/Inspections/ParameterCanBeByValInspectionTests.cs

Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -139,6 +139,32 @@ public void ParameterCanByByVal_DoesNotReturnResult_PassedByRefAndAssigned()
139139
Assert.AreEqual(0, inspectionResults.Count());
140140
}
141141

142+
[TestMethod]
143+
[TestCategory("Inspections")]
144+
public void ParameterCanByByVal_DoesNotReturnResult_BuiltInEventParam()
145+
{
146+
const string inputCode =
147+
@"Sub Foo(ByRef arg1 As String)
148+
arg1 = ""test""
149+
End Sub";
150+
151+
//Arrange
152+
var builder = new MockVbeBuilder();
153+
VBComponent component;
154+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
155+
var mockHost = new Mock<IHostApplication>();
156+
mockHost.SetupAllProperties();
157+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState());
158+
159+
parser.Parse();
160+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
161+
162+
var inspection = new ParameterCanBeByValInspection(parser.State);
163+
var inspectionResults = inspection.GetInspectionResults();
164+
165+
Assert.AreEqual(0, inspectionResults.Count());
166+
}
167+
142168
[TestMethod]
143169
[TestCategory("Inspections")]
144170
public void ParameterCanByByVal_ReturnsResult_SomeParams()

RubberduckTests/Inspections/ParameterNotUsedInspectionTests.cs

Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -92,6 +92,32 @@ public void ParameterUsed_DoesNotReturnResult()
9292
Assert.AreEqual(0, inspectionResults.Count());
9393
}
9494

95+
[TestMethod]
96+
[TestCategory("Inspections")]
97+
public void ParameterUsed_BuiltInEventHandlerParameter_DoesNotReturnResult()
98+
{
99+
const string inputCode =
100+
@"Private Sub UserForm_BeforeDropOrPaste(ByVal Cancel As MSForms.ReturnBoolean, ByVal Control As MSForms.Control, ByVal Action As MSForms.fmAction, ByVal Data As MSForms.DataObject, ByVal X As Single, ByVal Y As Single, ByVal Effect As MSForms.ReturnEffect, ByVal Shift As Integer)
101+
102+
End Sub";
103+
104+
//Arrange
105+
var builder = new MockVbeBuilder();
106+
VBComponent component;
107+
var vbe = builder.BuildFromSingleModule(inputCode, vbext_ComponentType.vbext_ct_MSForm, out component, new Rubberduck.VBEditor.Selection());
108+
var mockHost = new Mock<IHostApplication>();
109+
mockHost.SetupAllProperties();
110+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState());
111+
112+
parser.Parse();
113+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
114+
115+
var inspection = new ParameterNotUsedInspection(vbe.Object, parser.State, null);
116+
var inspectionResults = inspection.GetInspectionResults();
117+
118+
Assert.AreEqual(0, inspectionResults.Count());
119+
}
120+
95121
[TestMethod]
96122
[TestCategory("Inspections")]
97123
public void ParameterNotUsed_ReturnsResult_SomeParamsUsed()

RubberduckTests/Inspections/ProcedureNotUsedInspectionTests.cs

Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -194,6 +194,36 @@ Private Sub abc_Foo(ByVal arg1 As Integer, ByVal arg2 As String)
194194
Assert.AreEqual(0, inspectionResults.Count());
195195
}
196196

197+
[TestMethod]
198+
[TestCategory("Inspections")]
199+
public void ProcedureNotUsed_DoesNotReturnResult_BuiltInEventImplementation()
200+
{
201+
//Input
202+
const string inputCode =
203+
@"Private Sub UserForm_BeforeDropOrPaste(ByVal Cancel As MSForms.ReturnBoolean, ByVal Control As MSForms.Control, ByVal Action As MSForms.fmAction, ByVal Data As MSForms.DataObject, ByVal X As Single, ByVal Y As Single, ByVal Effect As MSForms.ReturnEffect, ByVal Shift As Integer)
204+
205+
End Sub";
206+
207+
//Arrange
208+
var builder = new MockVbeBuilder();
209+
var project = builder.ProjectBuilder("TestProject1", vbext_ProjectProtection.vbext_pp_none)
210+
.AddComponent("Form", vbext_ComponentType.vbext_ct_MSForm, inputCode)
211+
.Build();
212+
var vbe = builder.AddProject(project).Build();
213+
214+
var mockHost = new Mock<IHostApplication>();
215+
mockHost.SetupAllProperties();
216+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState());
217+
218+
parser.Parse();
219+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
220+
221+
var inspection = new ProcedureNotUsedInspection(parser.State);
222+
var inspectionResults = inspection.GetInspectionResults();
223+
224+
Assert.AreEqual(0, inspectionResults.Count());
225+
}
226+
197227
[TestMethod]
198228
[TestCategory("Inspections")]
199229
public void ProcedureNotUsed_NoResultForClassInitialize()

0 commit comments

Comments
 (0)