Skip to content

Commit 6e7c82a

Browse files
authored
Merge pull request #5592 from BZngr/MisleadingByRefParameter
Add MisleadingByRefParameterInspection
2 parents 3c10fca + 3e4a0c5 commit 6e7c82a

12 files changed

+268
-20
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 static 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)
Lines changed: 68 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,68 @@
1+
using Rubberduck.CodeAnalysis.Inspections.Abstract;
2+
using Rubberduck.Parsing.Symbols;
3+
using Rubberduck.Parsing.VBA;
4+
using Rubberduck.Parsing.VBA.DeclarationCaching;
5+
using Rubberduck.Resources.Inspections;
6+
using System.Linq;
7+
8+
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
9+
{
10+
/// <summary>
11+
/// Flags the value-parameter of a property mutators that are declared with an explict ByRef modifier.
12+
/// </summary>
13+
/// <why>
14+
/// Regardless of the presence or absence of an explicit ByRef or ByVal modifier, the value-parameter
15+
/// of a property mutator is always treated as though it had an explicit ByVal modifier.
16+
/// Exception: UserDefinedType parameters are always passed by reference.
17+
/// </why>
18+
/// <example hasResult="true">
19+
/// <module name="MyModule" type="Standard Module">
20+
/// <![CDATA[
21+
/// Private fizzField As Long
22+
/// Public Property Get Fizz() As Long
23+
/// Fizz = fizzFiled
24+
/// End Property
25+
/// Public Property Let Fizz(ByRef arg As Long)
26+
/// fizzFiled = arg
27+
/// End Property
28+
/// ]]>
29+
/// </module>
30+
/// </example>
31+
/// <example hasResult="false">
32+
/// <module name="MyModule" type="Standard Module">
33+
/// <![CDATA[
34+
/// Private fizzField As Long
35+
/// Public Property Get Fizz() As Long
36+
/// Fizz = fizzFiled
37+
/// End Property
38+
/// Public Property Let Fizz(arg As Long)
39+
/// fizzFiled = arg
40+
/// End Property
41+
/// ]]>
42+
/// </module>
43+
/// </example>
44+
internal sealed class MisleadingByRefParameterInspection : DeclarationInspectionBase
45+
{
46+
public MisleadingByRefParameterInspection(IDeclarationFinderProvider declarationFinderProvider)
47+
: base(declarationFinderProvider, DeclarationType.Parameter)
48+
{ }
49+
50+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
51+
{
52+
return declaration is ParameterDeclaration parameter
53+
&& !(parameter.AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.UserDefinedType) ?? false)
54+
&& parameter.ParentDeclaration is ModuleBodyElementDeclaration enclosingMethod
55+
&& (enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertyLet)
56+
|| enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertySet))
57+
&& enclosingMethod.Parameters.Last() == parameter
58+
&& parameter.IsByRef && !parameter.IsImplicitByRef;
59+
}
60+
61+
protected override string ResultDescription(Declaration declaration)
62+
{
63+
return string.Format(
64+
InspectionResults.MisleadingByRefParameterInspection,
65+
declaration.IdentifierName, declaration.ParentDeclaration.QualifiedName.MemberName);
66+
}
67+
}
68+
}

Rubberduck.CodeAnalysis/QuickFixes/Concrete/PassParameterByValueQuickFix.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ internal sealed class PassParameterByValueQuickFix : QuickFixBase
3838
private readonly IDeclarationFinderProvider _declarationFinderProvider;
3939

4040
public PassParameterByValueQuickFix(IDeclarationFinderProvider declarationFinderProvider)
41-
: base(typeof(ParameterCanBeByValInspection))
41+
: base(typeof(ParameterCanBeByValInspection), typeof(MisleadingByRefParameterInspection))
4242
{
4343
_declarationFinderProvider = declarationFinderProvider;
4444
}

Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs

Lines changed: 10 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Resources/Inspections/InspectionInfo.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -442,4 +442,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
442442
<data name="SuperfluousAnnotationArgumentInspection" xml:space="preserve">
443443
<value>An annotation has more arguments than allowed; superfluous arguments are ignored.</value>
444444
</data>
445+
<data name="MisleadingByRefParameterInspection" xml:space="preserve">
446+
<value>The last parameter (the 'Value' parameter) of property mutators are always passed ByVal. This is true regardless of the presence or absence of a ByRef or ByVal modifier. Exception: A UserDefinedType must always be passed ByRef even when it is the last parameter of a property mutator.</value>
447+
</data>
445448
</root>

Rubberduck.Resources/Inspections/InspectionNames.Designer.cs

Lines changed: 10 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Resources/Inspections/InspectionNames.resx

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -362,19 +362,15 @@
362362
</data>
363363
<data name="KeywordsUsedAsMemberInspection" xml:space="preserve">
364364
<value>Keyword used as member name</value>
365-
366365
</data>
367366
<data name="LineContinuationBetweenKeywordsInspection" xml:space="preserve">
368367
<value>Line continuation between keywords</value>
369-
370368
</data>
371369
<data name="NonBreakingSpaceIdentifierInspection" xml:space="preserve">
372370
<value>Identifier containing a non-breaking space</value>
373-
374371
</data>
375372
<data name="NegativeLineNumberInspection" xml:space="preserve">
376373
<value>Negative line number</value>
377-
378374
</data>
379375
<data name="OnErrorGoToMinusOneInspection" xml:space="preserve">
380376
<value>OnErrorGoto -1</value>
@@ -446,4 +442,7 @@
446442
<data name="SuperfluousAnnotationArgumentInspection" xml:space="preserve">
447443
<value>Superfluous annotation arguments</value>
448444
</data>
445+
<data name="MisleadingByRefParameterInspection" xml:space="preserve">
446+
<value>Misleading ByRef parameter modifier</value>
447+
</data>
449448
</root>

Rubberduck.Resources/Inspections/InspectionResults.Designer.cs

Lines changed: 10 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Resources/Inspections/InspectionResults.resx

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -513,4 +513,8 @@ In memoriam, 1972-2018</value>
513513
<value>The annotation '{0}' was expected to have less arguments.</value>
514514
<comment>{0} annotation name</comment>
515515
</data>
516+
<data name="MisleadingByRefParameterInspection" xml:space="preserve">
517+
<value>Misleading ByRef modifier used for parameter '{0}' ({1}).</value>
518+
<comment>{0} Parameter, {1} Member</comment>
519+
</data>
516520
</root>

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)