Skip to content

Commit d6bf85d

Browse files
authored
Merge pull request #4438 from comintern/bugfix
Misc bug fixes
2 parents ff42617 + cca1ccd commit d6bf85d

File tree

6 files changed

+192
-33
lines changed

6 files changed

+192
-33
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/HungarianNotationInspection.cs

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -94,8 +94,14 @@ public sealed class HungarianNotationInspection : InspectionBase
9494
DeclarationType.Variable
9595
};
9696

97+
private static readonly List<DeclarationType> IgnoredProcedureTypes = new List<DeclarationType>
98+
{
99+
DeclarationType.LibraryFunction,
100+
DeclarationType.LibraryProcedure
101+
};
102+
97103
#endregion
98-
104+
99105
private readonly IPersistanceService<CodeInspectionSettings> _settings;
100106

101107
public HungarianNotationInspection(RubberduckParserState state, IPersistanceService<CodeInspectionSettings> settings)
@@ -112,7 +118,10 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
112118
var hungarians = UserDeclarations
113119
.Where(declaration => !whitelistedNames.Contains(declaration.IdentifierName) &&
114120
TargetDeclarationTypes.Contains(declaration.DeclarationType) &&
115-
HungarianIdentifierRegex.IsMatch(declaration.IdentifierName))
121+
!IgnoredProcedureTypes.Contains(declaration.DeclarationType) &&
122+
!IgnoredProcedureTypes.Contains(declaration.ParentDeclaration.DeclarationType) &&
123+
HungarianIdentifierRegex.IsMatch(declaration.IdentifierName) &&
124+
!IsIgnoringInspectionResultFor(declaration, AnnotationName))
116125
.Select(issue => new DeclarationInspectionResult(this,
117126
string.Format(Resources.Inspections.InspectionResults.IdentifierNameInspection,
118127
RubberduckUI.ResourceManager.GetString($"DeclarationType_{issue.DeclarationType}", CultureInfo.CurrentUICulture),

Rubberduck.CodeAnalysis/Inspections/Concrete/MemberNotOnInterfaceInspection.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2121

2222
var targets = Declarations.Where(decl => decl.AsTypeDeclaration != null &&
2323
!decl.AsTypeDeclaration.IsUserDefined &&
24-
decl.AsTypeDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule) &&
24+
decl.AsTypeDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule) &&
2525
((ClassModuleDeclaration)decl.AsTypeDeclaration).IsExtensible)
2626
.SelectMany(decl => decl.References).ToList();
2727
return unresolved
@@ -33,7 +33,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3333
usage.Context.Parent.Parent.Equals(access.CallingContext))
3434
)
3535
})
36-
.Where(memberAccess => memberAccess.callingContext != null)
36+
.Where(memberAccess => memberAccess.callingContext != null &&
37+
memberAccess.callingContext.Declaration.DeclarationType != DeclarationType.Control) //TODO - remove this exception after resolving #2592)
3738
.Select(memberAccess => new DeclarationInspectionResult(this,
3839
string.Format(InspectionResults.MemberNotOnInterfaceInspection, memberAccess.access.IdentifierName,
3940
memberAccess.callingContext.Declaration.AsTypeDeclaration.IdentifierName), memberAccess.access));

Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs

Lines changed: 22 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,15 @@ public sealed class UnassignedVariableUsageInspection : InspectionBase
1818
public UnassignedVariableUsageInspection(RubberduckParserState state)
1919
: base(state) { }
2020

21+
//See https://github.com/rubberduck-vba/Rubberduck/issues/2010 for why these are being excluded.
22+
private static readonly List<string> IgnoredFunctions = new List<string>
23+
{
24+
"VBE7.DLL;VBA.Strings.Len",
25+
"VBE7.DLL;VBA.Strings.LenB",
26+
"VBA6.DLL;VBA.Strings.Len",
27+
"VBA6.DLL;VBA.Strings.LenB"
28+
};
29+
2130
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2231
{
2332
var declarations = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
@@ -27,41 +36,33 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2736
&& !declaration.IsSelfAssigned
2837
&& !declaration.References.Any(reference => reference.IsAssignment));
2938

30-
//See https://github.com/rubberduck-vba/Rubberduck/issues/2010 for why these are being excluded.
31-
//TODO: These need to be modified to correctly work in VB6.
32-
var lenFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.Len"));
33-
var lenbFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.LenB"));
39+
var excludedDeclarations = BuiltInDeclarations.Where(decl => IgnoredFunctions.Contains(decl.QualifiedName.ToString())).ToList();
3440

35-
return declarations.Where(d => d.References.Any() &&
36-
!DeclarationReferencesContainsReference(lenFunction, d) &&
37-
!DeclarationReferencesContainsReference(lenbFunction, d))
38-
.SelectMany(d => d.References)
39-
.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
40-
.Select(r => new IdentifierReferenceInspectionResult(this,
41-
string.Format(InspectionResults.UnassignedVariableUsageInspection, r.IdentifierName),
42-
State,
43-
r)).ToList();
41+
return declarations
42+
.Where(d => d.References.Any() && !excludedDeclarations.Any(excl => DeclarationReferencesContainsReference(excl, d)))
43+
.SelectMany(d => d.References)
44+
.Distinct()
45+
.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
46+
.Select(r => new IdentifierReferenceInspectionResult(this,
47+
string.Format(InspectionResults.UnassignedVariableUsageInspection, r.IdentifierName),
48+
State,
49+
r)).ToList();
4450
}
4551

46-
private bool DeclarationReferencesContainsReference(Declaration parentDeclaration, Declaration target)
52+
private static bool DeclarationReferencesContainsReference(Declaration parentDeclaration, Declaration target)
4753
{
48-
if (parentDeclaration == null)
49-
{
50-
return false;
51-
}
52-
5354
foreach (var targetReference in target.References)
5455
{
5556
foreach (var reference in parentDeclaration.References)
5657
{
57-
var context = (ParserRuleContext) reference.Context.Parent;
58+
var context = (ParserRuleContext)reference.Context.Parent;
5859
if (context.GetSelection().Contains(targetReference.Selection))
5960
{
6061
return true;
6162
}
6263
}
6364
}
64-
65+
6566
return false;
6667
}
6768
}

RubberduckTests/Inspections/HungarianNotationInspectionTests.cs

Lines changed: 67 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -200,12 +200,75 @@ Dim oRange As Object
200200

201201
[Test]
202202
[Category("Inspections")]
203-
public void InspectionName()
203+
public void HungarianNotation_DoesNotReturnResult_Ignored()
204204
{
205-
const string inspectionName = "UseMeaningfulNameInspection";
206-
var inspection = new UseMeaningfulNameInspection(null, null);
205+
const string inputCode =
206+
@"Sub Hungarian()
207+
'@Ignore HungarianNotation
208+
Dim oFoo As Object
209+
End Sub";
210+
211+
var builder = new MockVbeBuilder();
212+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
213+
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
214+
.Build();
215+
var vbe = builder.AddProject(project).Build();
216+
217+
using (var state = MockParser.CreateAndParse(vbe.Object))
218+
{
219+
var inspection = new HungarianNotationInspection(state, UseMeaningfulNameInspectionTests.GetInspectionSettings().Object);
220+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
221+
222+
Assert.AreEqual(0, inspectionResults.Count());
223+
}
224+
}
225+
226+
[Test]
227+
[Category("Inspections")]
228+
public void HungarianNotation_DoesNotReturnResult_LibraryFunctionParameters()
229+
{
230+
const string inputCode =
231+
@"
232+
Private Declare Function GetUserName Lib ""advapi32.dll"" Alias ""GetUserNameA"" (ByVal lpBuffer As String, nSize As Long) As Long
233+
";
234+
235+
var builder = new MockVbeBuilder();
236+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
237+
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
238+
.Build();
239+
var vbe = builder.AddProject(project).Build();
240+
241+
using (var state = MockParser.CreateAndParse(vbe.Object))
242+
{
243+
var inspection = new HungarianNotationInspection(state, UseMeaningfulNameInspectionTests.GetInspectionSettings().Object);
244+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
207245

208-
Assert.AreEqual(inspectionName, inspection.Name);
246+
Assert.AreEqual(0, inspectionResults.Count());
247+
}
248+
}
249+
250+
[Test]
251+
[Category("Inspections")]
252+
public void HungarianNotation_DoesNotReturnResult_LibraryFunction()
253+
{
254+
const string inputCode =
255+
@"
256+
Private Declare Sub chkVoid Lib ""somelib.dll"" Alias ""chkVoidA"" (number As Long)
257+
";
258+
259+
var builder = new MockVbeBuilder();
260+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
261+
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
262+
.Build();
263+
var vbe = builder.AddProject(project).Build();
264+
265+
using (var state = MockParser.CreateAndParse(vbe.Object))
266+
{
267+
var inspection = new HungarianNotationInspection(state, UseMeaningfulNameInspectionTests.GetInspectionSettings().Object);
268+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
269+
270+
Assert.AreEqual(0, inspectionResults.Count());
271+
}
209272
}
210273
}
211274
}

RubberduckTests/Inspections/MemberNotOnInterfaceInspectionTests.cs

Lines changed: 21 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -379,13 +379,30 @@ End Sub
379379
}
380380

381381
[Test]
382+
[Ignore("Test concurrency issue. Only passes if run individually.")]
382383
[Category("Inspections")]
383-
public void InspectionName()
384+
public void MemberNotOnInterface_DoesNotReturnResult_ControlObject()
384385
{
385-
const string inspectionName = "MemberNotOnInterfaceInspection";
386-
var inspection = new MemberNotOnInterfaceInspection(null);
386+
const string inputCode =
387+
@"Sub Foo(bar as MSForms.TextBox)
388+
Debug.Print bar.Left
389+
End Sub";
390+
391+
var vbeBuilder = new MockVbeBuilder();
392+
var projectBuilder = vbeBuilder.ProjectBuilder("testproject", ProjectProtection.Unprotected);
393+
projectBuilder.MockUserFormBuilder("UserForm1", inputCode).AddFormToProjectBuilder()
394+
.AddReference("MSForms", MockVbeBuilder.LibraryPathMsForms, 2, 0, true);
387395

388-
Assert.AreEqual(inspectionName, inspection.Name);
396+
vbeBuilder.AddProject(projectBuilder.Build());
397+
var vbe = vbeBuilder.Build();
398+
399+
using (var state = MockParser.CreateAndParse(vbe.Object))
400+
{
401+
var inspection = new MemberNotOnInterfaceInspection(state);
402+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
403+
404+
Assert.IsTrue(!inspectionResults.Any());
405+
}
389406
}
390407
}
391408
}

RubberduckTests/Inspections/UnassignedVariableUsageInspectionTests.cs

Lines changed: 68 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -112,6 +112,30 @@ Dim bb As Boolean
112112
}
113113
}
114114

115+
[Test]
116+
[Category("Inspections")]
117+
public void UnassignedVariableUsage_Ignored_DoesNotReturnResultMultipleIgnores()
118+
{
119+
const string inputCode =
120+
@"Sub Foo()
121+
Dim b As Boolean
122+
Dim bb As Boolean
123+
124+
'@Ignore UnassignedVariableUsage, VariableNotAssigned
125+
bb = b
126+
End Sub";
127+
128+
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
129+
using (var state = MockParser.CreateAndParse(vbe.Object))
130+
{
131+
132+
var inspection = new UnassignedVariableUsageInspection(state);
133+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
134+
135+
Assert.IsFalse(inspectionResults.Any());
136+
}
137+
}
138+
115139
[Test]
116140
[Category("Inspections")]
117141
public void UnassignedVariableUsage_NoResultIfNoReferences()
@@ -132,6 +156,50 @@ Dim foo
132156
}
133157
}
134158

159+
[Test]
160+
[Ignore("Test concurrency issue. Only passes if run individually.")]
161+
[Category("Inspections")]
162+
public void UnassignedVariableUsage_NoResultForLenFunction()
163+
{
164+
const string inputCode =
165+
@"Sub DoSomething()
166+
Dim foo As LongPtr
167+
Debug.Print Len(foo)
168+
End Sub";
169+
170+
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
171+
using (var state = MockParser.CreateAndParse(vbe.Object))
172+
{
173+
174+
var inspection = new UnassignedVariableUsageInspection(state);
175+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
176+
177+
Assert.IsFalse(inspectionResults.Any());
178+
}
179+
}
180+
181+
[Test]
182+
[Ignore("Test concurrency issue. Only passes if run individually.")]
183+
[Category("Inspections")]
184+
public void UnassignedVariableUsage_NoResultForLenBFunction()
185+
{
186+
const string inputCode =
187+
@"Sub DoSomething()
188+
Dim foo As LongPtr
189+
Debug.Print LenB(foo)
190+
End Sub";
191+
192+
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
193+
using (var state = MockParser.CreateAndParse(vbe.Object))
194+
{
195+
196+
var inspection = new UnassignedVariableUsageInspection(state);
197+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
198+
199+
Assert.IsFalse(inspectionResults.Any());
200+
}
201+
}
202+
135203
[Test]
136204
[Category("Inspections")]
137205
public void InspectionName()

0 commit comments

Comments
 (0)