Skip to content

Commit 660aa9a

Browse files
committed
Add MisleadingByRefParameterInspection
1 parent 136889f commit 660aa9a

File tree

10 files changed

+207
-8
lines changed

10 files changed

+207
-8
lines changed
Lines changed: 72 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,72 @@
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+
if ((declaration is ParameterDeclaration parameter)
53+
&& parameter.ParentDeclaration is ModuleBodyElementDeclaration enclosingMethod
54+
&& (enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertyLet)
55+
|| enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertySet))
56+
&& enclosingMethod.Parameters.Last() == parameter
57+
&& !(parameter.AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.UserDefinedType) ?? false))
58+
{
59+
return parameter.IsByRef && !parameter.IsImplicitByRef;
60+
}
61+
62+
return false;
63+
}
64+
65+
protected override string ResultDescription(Declaration declaration)
66+
{
67+
return string.Format(
68+
InspectionResults.MisleadingByRefParameterInspection,
69+
declaration.IdentifierName);
70+
}
71+
}
72+
}

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 by value. This is true regardless of the presence or absence of a ByVal modifier. Exception: UserDefinedType parameters must always be passed by reference in all cases.</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>ByRef is a misleading modifier because the parameter will be passed ByVal.</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}'.</value>
518+
<comment>{0} Parameter name</comment>
519+
</data>
516520
</root>
Lines changed: 72 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,72 @@
1+
using NUnit.Framework;
2+
using Rubberduck.CodeAnalysis.Inspections;
3+
using Rubberduck.CodeAnalysis.Inspections.Concrete;
4+
using Rubberduck.Parsing.VBA;
5+
using System;
6+
using System.Collections.Generic;
7+
using System.Linq;
8+
using System.Text;
9+
using System.Threading.Tasks;
10+
11+
namespace RubberduckTests.Inspections
12+
{
13+
[TestFixture]
14+
public class MisleadingByRefParameterInspectionTests : InspectionTestsBase
15+
{
16+
[TestCase("Property Let Fizz(ByRef arg1 As Integer)\r\nEnd Property", 1)]
17+
[TestCase("Property Let Fizz(arg1 As Integer)\r\nEnd Property", 0)]
18+
[TestCase("Property Let Fizz(ByVal arg1 As Integer)\r\nEnd Property", 0)]
19+
[TestCase("Property Set Fizz(ByRef arg1 As Object)\r\nEnd Property", 1)]
20+
[TestCase("Property Set Fizz(arg1 As Object)\r\nEnd Property", 0)]
21+
[TestCase("Property Set Fizz(ByVal arg1 As Object)\r\nEnd Property", 0)]
22+
[Category("QuickFixes")]
23+
[Category(nameof(MisleadingByRefParameterInspection))]
24+
public void AllParamMechanisms(string inputCode, int expectedCount)
25+
{
26+
Assert.AreEqual(expectedCount, InspectionResultsForStandardModule(inputCode).Count());
27+
}
28+
29+
[TestCase("arg")]
30+
[TestCase("ByRef arg")]
31+
[Category("QuickFixes")]
32+
[Category(nameof(MisleadingByRefParameterInspection))]
33+
public void UserDefinedTypeEdgeCase(string parameterMechanismAndParam)
34+
{
35+
var inputCode =
36+
$@"
37+
Option Explicit
38+
39+
Public Type TestType
40+
FirstValue As Long
41+
End Type
42+
43+
Private this As TestType
44+
45+
Public Property Get UserDefinedType() As TestType
46+
UserDefinedType = this
47+
End Property
48+
49+
Public Property Let UserDefinedType({parameterMechanismAndParam} As TestType)
50+
this = arg
51+
End Property
52+
";
53+
54+
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
55+
}
56+
57+
[Test]
58+
[Category("QuickFixes")]
59+
[Category(nameof(MisleadingByRefParameterInspection))]
60+
public void InspectionName()
61+
{
62+
var inspection = new MisleadingByRefParameterInspection(null);
63+
64+
Assert.AreEqual(nameof(MisleadingByRefParameterInspection), inspection.Name);
65+
}
66+
67+
protected override IInspection InspectionUnderTest(RubberduckParserState state)
68+
{
69+
return new MisleadingByRefParameterInspection(state);
70+
}
71+
}
72+
}

RubberduckTests/QuickFixes/PassParameterByValueQuickFixTests.cs

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -296,6 +296,28 @@ Debug.Print foo
296296
Assert.AreEqual(expectedCode, actualCode);
297297
}
298298

299+
[Test]
300+
[Category("QuickFixes")]
301+
[Category(nameof(MisleadingByRefParameterInspection))]
302+
public void CorrectsMisleadingByRefPropertyMutatorParameter()
303+
{
304+
const string inputCode =
305+
@"
306+
Option Explicit
307+
308+
Private fizzField As Long
309+
310+
Public Property Get Fizz() As Long
311+
Fizz = fizzField
312+
End Property
313+
314+
Public Property Let Fizz(ByRef arg As Long)
315+
fizzField = arg
316+
End Property
317+
";
318+
var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new MisleadingByRefParameterInspection(state));
319+
StringAssert.Contains("Public Property Let Fizz(ByVal arg As Long)", actualCode);
320+
}
299321

300322
protected override IQuickFix QuickFix(RubberduckParserState state)
301323
{

0 commit comments

Comments
 (0)