Skip to content

Commit 9ba28b2

Browse files
committed
Ignore Property mutator Value param
1 parent 660aa9a commit 9ba28b2

File tree

2 files changed

+65
-12
lines changed

2 files changed

+65
-12
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitByRefModifierInspection.cs

Lines changed: 28 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -3,15 +3,19 @@
33
using Rubberduck.Parsing.VBA;
44
using Rubberduck.Parsing.VBA.DeclarationCaching;
55
using Rubberduck.Resources.Inspections;
6+
using System.Linq;
67

78
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
89
{
910
/// <summary>
1011
/// Highlights implicit ByRef modifiers in user code.
1112
/// </summary>
1213
/// <why>
13-
/// In modern VB (VB.NET), the implicit modifier is ByVal, as it is in most other programming languages.
14-
/// Making the ByRef modifiers explicit can help surface potentially unexpected language defaults.
14+
/// VBA parameters are implicitly ByRef, which differs from modern VB (VB.NET) and most other programming languages which are implicitly ByVal.
15+
/// So, explicitly identifing VBA parameter mechanisms (the ByRef and ByVal modifiers) can help surface potentially unexpected language results.
16+
/// The inspection does not flag an implicit parameter mechanism for the last parameter of Property mutators (Let or Set).
17+
/// VBA applies a ByVal parameter mechanism to the last parameter in the absence (or presence!) of a modifier.
18+
/// Exception: UserDefinedType parameters must always be passed as ByRef.
1519
/// </why>
1620
/// <example hasResult="true">
1721
/// <module name="MyModule" type="Standard Module">
@@ -31,6 +35,16 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
3135
/// ]]>
3236
/// </module>
3337
/// </example>
38+
/// <example hasResult="false">
39+
/// <module name="MyModule" type="Standard Module">
40+
/// <![CDATA[
41+
/// Private theLength As Long
42+
/// Public Property Let Length(newLength As Long)
43+
/// theLength = newLength
44+
/// End Sub
45+
/// ]]>
46+
/// </module>
47+
/// </example>
3448
internal sealed class ImplicitByRefModifierInspection : DeclarationInspectionBase
3549
{
3650
public ImplicitByRefModifierInspection(IDeclarationFinderProvider declarationFinderProvider)
@@ -41,21 +55,23 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
4155
{
4256
if (!(declaration is ParameterDeclaration parameter)
4357
|| !parameter.IsImplicitByRef
44-
|| parameter.IsParamArray)
58+
|| parameter.IsParamArray
59+
//Exclude parameters of Declare statements
60+
|| !(parameter.ParentDeclaration is ModuleBodyElementDeclaration enclosingMethod))
4561
{
4662
return false;
4763
}
4864

49-
var parentDeclaration = parameter.ParentDeclaration;
50-
51-
if (parentDeclaration is ModuleBodyElementDeclaration enclosingMethod)
52-
{
53-
return !enclosingMethod.IsInterfaceImplementation
54-
&& !finder.FindEventHandlers().Contains(enclosingMethod);
55-
}
65+
return !IsPropertyMutatorRHSParameter(enclosingMethod, parameter)
66+
&& !enclosingMethod.IsInterfaceImplementation
67+
&& !finder.FindEventHandlers().Contains(enclosingMethod);
68+
}
5669

57-
return parentDeclaration.DeclarationType != DeclarationType.LibraryFunction
58-
&& parentDeclaration.DeclarationType != DeclarationType.LibraryProcedure;
70+
private bool IsPropertyMutatorRHSParameter(ModuleBodyElementDeclaration enclosingMethod, ParameterDeclaration implicitByRefParameter)
71+
{
72+
return (enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertyLet)
73+
|| enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertySet))
74+
&& enclosingMethod.Parameters.Last().Equals(implicitByRefParameter);
5975
}
6076

6177
protected override string ResultDescription(Declaration declaration)

RubberduckTests/Inspections/ImplicitByRefModifierInspectionTests.cs

Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,13 +17,26 @@ public class ImplicitByRefModifierInspectionTests : InspectionTestsBase
1717
[TestCase("Sub Foo(arg1 As Integer, ByRef arg2 As Date)\r\nEnd Sub", 1)]
1818
[TestCase("Sub Foo(ParamArray arg1 As Integer)\r\nEnd Sub", 0)]
1919
[Category("QuickFixes")]
20+
[Category(nameof(ImplicitByRefModifierInspection))]
2021
public void ImplicitByRefModifier_SimpleScenarios(string inputCode, int expectedCount)
2122
{
2223
Assert.AreEqual(expectedCount, InspectionResultsForStandardModule(inputCode).Count());
2324
}
2425

26+
[TestCase("Property Let Fizz(RHS As Integer)\r\nEnd Property", 0)]
27+
[TestCase("Property Set Fizz(RHS As Object)\r\nEnd Property", 0)]
28+
[TestCase("Property Let Fizz(index As Integer, RHS As Integer)\r\nEnd Property", 1)]
29+
[TestCase("Property Set Fizz(index As Integer, RHS As Object)\r\nEnd Property", 1)]
30+
[Category("QuickFixes")]
31+
[Category(nameof(ImplicitByRefModifierInspection))]
32+
public void ImplicitByRefModifier_PropertyMutatorRHSParameter(string inputCode, int expectedCount)
33+
{
34+
Assert.AreEqual(expectedCount, InspectionResultsForStandardModule(inputCode).Count());
35+
}
36+
2537
[Test]
2638
[Category("QuickFixes")]
39+
[Category(nameof(ImplicitByRefModifierInspection))]
2740
public void ImplicitByRefModifier_ReturnsResult_InterfaceImplementation()
2841
{
2942
const string inputCode1 =
@@ -47,6 +60,7 @@ Sub IClass1_Foo(arg1 As Integer)
4760

4861
[Test]
4962
[Category("QuickFixes")]
63+
[Category(nameof(ImplicitByRefModifierInspection))]
5064
public void ImplicitByRefModifier_ReturnsResult_MultipleInterfaceImplementations()
5165
{
5266
const string inputCode1 =
@@ -77,6 +91,7 @@ Sub IClass1_Foo(arg1 As Integer)
7791

7892
[Test]
7993
[Category("QuickFixes")]
94+
[Category(nameof(ImplicitByRefModifierInspection))]
8095
public void ImplicitByRefModifier_Ignored_DoesNotReturnResult()
8196
{
8297
const string inputCode =
@@ -86,8 +101,30 @@ Sub Foo(arg1 As Integer)
86101
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
87102
}
88103

104+
[TestCase(@"Public Declare PtrSafe Sub LibProcedure Lib ""MyLib""(arg As Long)", "LibProcedure 2000")]
105+
[TestCase(@"Public Declare PtrSafe Function LibProcedure Lib ""MyLib""(arg As Long) As Long", "test = LibProcedure(2000)")]
106+
[Category("QuickFixes")]
107+
[Category(nameof(ImplicitByRefModifierInspection))]
108+
public void ImplicitByRefModifier_IgnoresDeclareStatement(string declareStatement, string libraryCall)
109+
{
110+
var inputCode =
111+
$@"
112+
Option Explicit
113+
114+
Private test As Long
115+
116+
{declareStatement}
117+
118+
Public Sub CallTheLib()
119+
{libraryCall}
120+
End Sub";
121+
122+
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
123+
}
124+
89125
[Test]
90126
[Category("QuickFixes")]
127+
[Category(nameof(ImplicitByRefModifierInspection))]
91128
public void InspectionName()
92129
{
93130
var inspection = new ImplicitByRefModifierInspection(null);

0 commit comments

Comments
 (0)