Skip to content

Commit

Permalink
Merge pull request #5592 from BZngr/MisleadingByRefParameter
Browse files Browse the repository at this point in the history
Add MisleadingByRefParameterInspection
  • Loading branch information
bclothier committed Oct 24, 2020
2 parents 3c10fca + 3e4a0c5 commit 6e7c82a
Show file tree
Hide file tree
Showing 12 changed files with 268 additions and 20 deletions.
Expand Up @@ -3,15 +3,19 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using System.Linq;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Highlights implicit ByRef modifiers in user code.
/// </summary>
/// <why>
/// In modern VB (VB.NET), the implicit modifier is ByVal, as it is in most other programming languages.
/// Making the ByRef modifiers explicit can help surface potentially unexpected language defaults.
/// VBA parameters are implicitly ByRef, which differs from modern VB (VB.NET) and most other programming languages which are implicitly ByVal.
/// So, explicitly identifing VBA parameter mechanisms (the ByRef and ByVal modifiers) can help surface potentially unexpected language results.
/// The inspection does not flag an implicit parameter mechanism for the last parameter of Property mutators (Let or Set).
/// VBA applies a ByVal parameter mechanism to the last parameter in the absence (or presence!) of a modifier.
/// Exception: UserDefinedType parameters must always be passed as ByRef.
/// </why>
/// <example hasResult="true">
/// <module name="MyModule" type="Standard Module">
Expand All @@ -31,6 +35,16 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="MyModule" type="Standard Module">
/// <![CDATA[
/// Private theLength As Long
/// Public Property Let Length(newLength As Long)
/// theLength = newLength
/// End Sub
/// ]]>
/// </module>
/// </example>
internal sealed class ImplicitByRefModifierInspection : DeclarationInspectionBase
{
public ImplicitByRefModifierInspection(IDeclarationFinderProvider declarationFinderProvider)
Expand All @@ -41,21 +55,23 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
{
if (!(declaration is ParameterDeclaration parameter)
|| !parameter.IsImplicitByRef
|| parameter.IsParamArray)
|| parameter.IsParamArray
//Exclude parameters of Declare statements
|| !(parameter.ParentDeclaration is ModuleBodyElementDeclaration enclosingMethod))
{
return false;
}

var parentDeclaration = parameter.ParentDeclaration;

if (parentDeclaration is ModuleBodyElementDeclaration enclosingMethod)
{
return !enclosingMethod.IsInterfaceImplementation
&& !finder.FindEventHandlers().Contains(enclosingMethod);
}
return !IsPropertyMutatorRHSParameter(enclosingMethod, parameter)
&& !enclosingMethod.IsInterfaceImplementation
&& !finder.FindEventHandlers().Contains(enclosingMethod);
}

return parentDeclaration.DeclarationType != DeclarationType.LibraryFunction
&& parentDeclaration.DeclarationType != DeclarationType.LibraryProcedure;
private static bool IsPropertyMutatorRHSParameter(ModuleBodyElementDeclaration enclosingMethod, ParameterDeclaration implicitByRefParameter)
{
return (enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertyLet)
|| enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertySet))
&& enclosingMethod.Parameters.Last().Equals(implicitByRefParameter);
}

protected override string ResultDescription(Declaration declaration)
Expand Down
@@ -0,0 +1,68 @@
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using System.Linq;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Flags the value-parameter of a property mutators that are declared with an explict ByRef modifier.
/// </summary>
/// <why>
/// Regardless of the presence or absence of an explicit ByRef or ByVal modifier, the value-parameter
/// of a property mutator is always treated as though it had an explicit ByVal modifier.
/// Exception: UserDefinedType parameters are always passed by reference.
/// </why>
/// <example hasResult="true">
/// <module name="MyModule" type="Standard Module">
/// <![CDATA[
/// Private fizzField As Long
/// Public Property Get Fizz() As Long
/// Fizz = fizzFiled
/// End Property
/// Public Property Let Fizz(ByRef arg As Long)
/// fizzFiled = arg
/// End Property
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="MyModule" type="Standard Module">
/// <![CDATA[
/// Private fizzField As Long
/// Public Property Get Fizz() As Long
/// Fizz = fizzFiled
/// End Property
/// Public Property Let Fizz(arg As Long)
/// fizzFiled = arg
/// End Property
/// ]]>
/// </module>
/// </example>
internal sealed class MisleadingByRefParameterInspection : DeclarationInspectionBase
{
public MisleadingByRefParameterInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Parameter)
{ }

protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
return declaration is ParameterDeclaration parameter
&& !(parameter.AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.UserDefinedType) ?? false)
&& parameter.ParentDeclaration is ModuleBodyElementDeclaration enclosingMethod
&& (enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertyLet)
|| enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertySet))
&& enclosingMethod.Parameters.Last() == parameter
&& parameter.IsByRef && !parameter.IsImplicitByRef;
}

protected override string ResultDescription(Declaration declaration)
{
return string.Format(
InspectionResults.MisleadingByRefParameterInspection,
declaration.IdentifierName, declaration.ParentDeclaration.QualifiedName.MemberName);
}
}
}
Expand Up @@ -38,7 +38,7 @@ internal sealed class PassParameterByValueQuickFix : QuickFixBase
private readonly IDeclarationFinderProvider _declarationFinderProvider;

public PassParameterByValueQuickFix(IDeclarationFinderProvider declarationFinderProvider)
: base(typeof(ParameterCanBeByValInspection))
: base(typeof(ParameterCanBeByValInspection), typeof(MisleadingByRefParameterInspection))
{
_declarationFinderProvider = declarationFinderProvider;
}
Expand Down
11 changes: 10 additions & 1 deletion Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

3 changes: 3 additions & 0 deletions Rubberduck.Resources/Inspections/InspectionInfo.resx
Expand Up @@ -442,4 +442,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
<data name="SuperfluousAnnotationArgumentInspection" xml:space="preserve">
<value>An annotation has more arguments than allowed; superfluous arguments are ignored.</value>
</data>
<data name="MisleadingByRefParameterInspection" xml:space="preserve">
<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>
</data>
</root>
11 changes: 10 additions & 1 deletion Rubberduck.Resources/Inspections/InspectionNames.Designer.cs

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

7 changes: 3 additions & 4 deletions Rubberduck.Resources/Inspections/InspectionNames.resx
Expand Up @@ -362,19 +362,15 @@
</data>
<data name="KeywordsUsedAsMemberInspection" xml:space="preserve">
<value>Keyword used as member name</value>

</data>
<data name="LineContinuationBetweenKeywordsInspection" xml:space="preserve">
<value>Line continuation between keywords</value>

</data>
<data name="NonBreakingSpaceIdentifierInspection" xml:space="preserve">
<value>Identifier containing a non-breaking space</value>

</data>
<data name="NegativeLineNumberInspection" xml:space="preserve">
<value>Negative line number</value>

</data>
<data name="OnErrorGoToMinusOneInspection" xml:space="preserve">
<value>OnErrorGoto -1</value>
Expand Down Expand Up @@ -446,4 +442,7 @@
<data name="SuperfluousAnnotationArgumentInspection" xml:space="preserve">
<value>Superfluous annotation arguments</value>
</data>
<data name="MisleadingByRefParameterInspection" xml:space="preserve">
<value>Misleading ByRef parameter modifier</value>
</data>
</root>
11 changes: 10 additions & 1 deletion Rubberduck.Resources/Inspections/InspectionResults.Designer.cs

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 4 additions & 0 deletions Rubberduck.Resources/Inspections/InspectionResults.resx
Expand Up @@ -513,4 +513,8 @@ In memoriam, 1972-2018</value>
<value>The annotation '{0}' was expected to have less arguments.</value>
<comment>{0} annotation name</comment>
</data>
<data name="MisleadingByRefParameterInspection" xml:space="preserve">
<value>Misleading ByRef modifier used for parameter '{0}' ({1}).</value>
<comment>{0} Parameter, {1} Member</comment>
</data>
</root>
Expand Up @@ -17,13 +17,26 @@ public class ImplicitByRefModifierInspectionTests : InspectionTestsBase
[TestCase("Sub Foo(arg1 As Integer, ByRef arg2 As Date)\r\nEnd Sub", 1)]
[TestCase("Sub Foo(ParamArray arg1 As Integer)\r\nEnd Sub", 0)]
[Category("QuickFixes")]
[Category(nameof(ImplicitByRefModifierInspection))]
public void ImplicitByRefModifier_SimpleScenarios(string inputCode, int expectedCount)
{
Assert.AreEqual(expectedCount, InspectionResultsForStandardModule(inputCode).Count());
}

[TestCase("Property Let Fizz(RHS As Integer)\r\nEnd Property", 0)]
[TestCase("Property Set Fizz(RHS As Object)\r\nEnd Property", 0)]
[TestCase("Property Let Fizz(index As Integer, RHS As Integer)\r\nEnd Property", 1)]
[TestCase("Property Set Fizz(index As Integer, RHS As Object)\r\nEnd Property", 1)]
[Category("QuickFixes")]
[Category(nameof(ImplicitByRefModifierInspection))]
public void ImplicitByRefModifier_PropertyMutatorRHSParameter(string inputCode, int expectedCount)
{
Assert.AreEqual(expectedCount, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("QuickFixes")]
[Category(nameof(ImplicitByRefModifierInspection))]
public void ImplicitByRefModifier_ReturnsResult_InterfaceImplementation()
{
const string inputCode1 =
Expand All @@ -47,6 +60,7 @@ Sub IClass1_Foo(arg1 As Integer)

[Test]
[Category("QuickFixes")]
[Category(nameof(ImplicitByRefModifierInspection))]
public void ImplicitByRefModifier_ReturnsResult_MultipleInterfaceImplementations()
{
const string inputCode1 =
Expand Down Expand Up @@ -77,6 +91,7 @@ Sub IClass1_Foo(arg1 As Integer)

[Test]
[Category("QuickFixes")]
[Category(nameof(ImplicitByRefModifierInspection))]
public void ImplicitByRefModifier_Ignored_DoesNotReturnResult()
{
const string inputCode =
Expand All @@ -86,8 +101,30 @@ Sub Foo(arg1 As Integer)
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

[TestCase(@"Public Declare PtrSafe Sub LibProcedure Lib ""MyLib""(arg As Long)", "LibProcedure 2000")]
[TestCase(@"Public Declare PtrSafe Function LibProcedure Lib ""MyLib""(arg As Long) As Long", "test = LibProcedure(2000)")]
[Category("QuickFixes")]
[Category(nameof(ImplicitByRefModifierInspection))]
public void ImplicitByRefModifier_IgnoresDeclareStatement(string declareStatement, string libraryCall)
{
var inputCode =
$@"
Option Explicit
Private test As Long
{declareStatement}
Public Sub CallTheLib()
{libraryCall}
End Sub";

Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("QuickFixes")]
[Category(nameof(ImplicitByRefModifierInspection))]
public void InspectionName()
{
var inspection = new ImplicitByRefModifierInspection(null);
Expand Down

0 comments on commit 6e7c82a

Please sign in to comment.