Skip to content

Commit 74d66d2

Browse files
authored
Merge pull request #5533 from MDoerner/EnhanceFunctionReturnValueDiscardedInspectionForBuiltInFunctions
Disable FunctionReturnValueDiscardedInspection for functions not defined in user code.
2 parents 2581512 + 9fcad5a commit 74d66d2

File tree

2 files changed

+20
-6
lines changed

2 files changed

+20
-6
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueDiscardedInspection.cs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -53,11 +53,12 @@ public FunctionReturnValueDiscardedInspection(IDeclarationFinderProvider declara
5353
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
5454
{
5555
return reference?.Declaration != null
56-
&& !reference.IsAssignment
57-
&& !reference.IsArrayAccess
58-
&& !reference.IsInnerRecursiveDefaultMemberAccess
59-
&& reference.Declaration.DeclarationType == DeclarationType.Function
60-
&& IsCalledAsProcedure(reference.Context);
56+
&& reference.Declaration.IsUserDefined
57+
&& !reference.IsAssignment
58+
&& !reference.IsArrayAccess
59+
&& !reference.IsInnerRecursiveDefaultMemberAccess
60+
&& reference.Declaration.DeclarationType == DeclarationType.Function
61+
&& IsCalledAsProcedure(reference.Context);
6162
}
6263

6364
private static bool IsCalledAsProcedure(ParserRuleContext context)

RubberduckTests/Inspections/FunctionReturnValueDiscardedInspectionTests.cs

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Rubberduck.CodeAnalysis.Inspections.Concrete;
55
using Rubberduck.Parsing.VBA;
66
using Rubberduck.VBEditor.SafeComWrappers;
7+
using RubberduckTests.Mocks;
78

89
namespace RubberduckTests.Inspections
910
{
@@ -308,8 +309,20 @@ Public Sub Dummy()
308309
MsgBox ""Test""
309310
Workbooks.Add
310311
End Sub
312+
313+
Public Sub Baz()
314+
Err.Raise -1, ""Foo"", ""Bar""
315+
End Sub
311316
";
312-
Assert.AreEqual(0, InspectionResultsForStandardModule(code).Count());
317+
var vbe = new MockVbeBuilder()
318+
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
319+
.AddComponent("TestModule", ComponentType.StandardModule, code)
320+
.AddReference(ReferenceLibrary.VBA)
321+
.AddReference(ReferenceLibrary.Excel)
322+
.AddProjectToVbeBuilder()
323+
.Build()
324+
.Object;
325+
Assert.AreEqual(0, InspectionResults(vbe).Count());
313326
}
314327

315328
[Test]

0 commit comments

Comments
 (0)