Skip to content

Commit

Permalink
Fix inspection false positive for array parameters
Browse files Browse the repository at this point in the history
  • Loading branch information
BZngr committed Dec 3, 2020
1 parent 06f5b03 commit bb030cf
Show file tree
Hide file tree
Showing 2 changed files with 31 additions and 2 deletions.
Expand Up @@ -50,14 +50,18 @@ public MisleadingByRefParameterInspection(IDeclarationFinderProvider declaration
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
&& !IsAlwaysByRef(declaration)
&& declaration.ParentDeclaration is ModuleBodyElementDeclaration enclosingMethod
&& (enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertyLet)
|| enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertySet))
&& enclosingMethod.Parameters.Last() == parameter
&& parameter.IsByRef && !parameter.IsImplicitByRef;
}

private static bool IsAlwaysByRef(Declaration parameter)
=> parameter.IsArray
|| (parameter.AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.UserDefinedType) ?? false);

protected override string ResultDescription(Declaration declaration)
{
return string.Format(
Expand Down
Expand Up @@ -54,6 +54,31 @@ End Property
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

//https://github.com/rubberduck-vba/Rubberduck/issues/5628
[TestCase("ArrayToStore")]
[TestCase("ByRef ArrayToStore")]
[Category("QuickFixes")]
[Category(nameof(MisleadingByRefParameterInspection))]
public void ArrayEdgeCase(string parameterMechanismAndParam)
{
var inputCode =
$@"
Option Explicit
Private InternalArray() As Variant
Public Property Get StoredArray() As Variant()
StoredArray = InternalArray
End Property
Public Property Let StoredArray({parameterMechanismAndParam}() As Variant)
InternalArray = ArrayToStore
End Property
";

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

[Test]
[Category("QuickFixes")]
[Category(nameof(MisleadingByRefParameterInspection))]
Expand Down

0 comments on commit bb030cf

Please sign in to comment.