Skip to content

Commit

Permalink
Merge pull request #4488 from comintern/validref
Browse files Browse the repository at this point in the history
Add new inspection for Excel UDFs hidden by cells.
  • Loading branch information
retailcoder committed Nov 17, 2018
2 parents 83e94b2 + 3643c7e commit fb0f9b7
Show file tree
Hide file tree
Showing 14 changed files with 799 additions and 921 deletions.
@@ -0,0 +1,49 @@
using System;
using System.Collections.Generic;
using System.Linq;
using System.Text.RegularExpressions;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.Inspections;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.Inspections.Inspections.Concrete
{
[RequiredLibrary("Excel")]
public class ExcelUdfNameIsValidCellReferenceInspection : InspectionBase
{
public ExcelUdfNameIsValidCellReferenceInspection(RubberduckParserState state) : base(state) { }

private static readonly Regex ValidCellIdRegex =
new Regex(@"^([a-z]|[a-z]{2}|[a-w][a-z]{2}|x([a-e][a-z]|f[a-d]))(?<Row>\d+)$",
RegexOptions.Compiled | RegexOptions.IgnoreCase | RegexOptions.ExplicitCapture);

private static readonly HashSet<Accessibility> VisibleAsUdf = new HashSet<Accessibility> { Accessibility.Public, Accessibility.Implicit };

private const uint MaximumExcelRows = 1048576;

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var excel = State.DeclarationFinder.Projects.SingleOrDefault(item => !item.IsUserDefined && item.IdentifierName == "Excel");
if (excel == null)
{
return Enumerable.Empty<IInspectionResult>();
}

var candidates = UserDeclarations.OfType<FunctionDeclaration>().Where(decl =>
decl.ParentScopeDeclaration.DeclarationType == DeclarationType.ProceduralModule &&
VisibleAsUdf.Contains(decl.Accessibility));

return (from function in candidates.Where(decl => ValidCellIdRegex.IsMatch(decl.IdentifierName))
let row = Convert.ToUInt32(ValidCellIdRegex.Matches(function.IdentifierName)[0].Groups["Row"].Value)
where row > 0 && row <= MaximumExcelRows && !IsIgnoringInspectionResultFor(function, AnnotationName)
select new DeclarationInspectionResult(this,
string.Format(InspectionResults.ExcelUdfNameIsValidCellReferenceInspection, function.IdentifierName),
function))
.Cast<IInspectionResult>().ToList();
}
}
}
@@ -1,6 +1,7 @@
using System.Globalization;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Concrete;
using Rubberduck.Inspections.Inspections.Concrete;
using Rubberduck.Interaction;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.Rewriter;
Expand All @@ -20,7 +21,11 @@ public sealed class RenameDeclarationQuickFix : QuickFixBase
private readonly IMessageBox _messageBox;

public RenameDeclarationQuickFix(IVBE vbe, RubberduckParserState state, IMessageBox messageBox, IRewritingManager rewritingManager)
: base(typeof(HungarianNotationInspection), typeof(UseMeaningfulNameInspection), typeof(DefaultProjectNameInspection), typeof(UnderscoreInPublicClassModuleMemberInspection))
: base(typeof(HungarianNotationInspection),
typeof(UseMeaningfulNameInspection),
typeof(DefaultProjectNameInspection),
typeof(UnderscoreInPublicClassModuleMemberInspection),
typeof(ExcelUdfNameIsValidCellReferenceInspection))
{
_vbe = vbe;
_state = state;
Expand Down
585 changes: 300 additions & 285 deletions Rubberduck.Core/Properties/Settings.Designer.cs

Large diffs are not rendered by default.

493 changes: 257 additions & 236 deletions Rubberduck.Core/Properties/Settings.settings

Large diffs are not rendered by default.

13 changes: 13 additions & 0 deletions Rubberduck.Core/Rubberduck.Core.csproj
Expand Up @@ -81,4 +81,17 @@
<Version>2.0.20525</Version>
</PackageReference>
</ItemGroup>
<ItemGroup>
<Compile Update="Properties\Settings.Designer.cs">
<DesignTime>True</DesignTime>
<AutoGen>True</AutoGen>
<DependentUpon>Settings.settings</DependentUpon>
</Compile>
</ItemGroup>
<ItemGroup>
<None Update="Properties\Settings.settings">
<Generator>SettingsSingleFileGenerator</Generator>
<LastGenOutput>Settings.Designer.cs</LastGenOutput>
</None>
</ItemGroup>
</Project>
399 changes: 0 additions & 399 deletions Rubberduck.Core/app.config

Large diffs are not rendered by default.

9 changes: 9 additions & 0 deletions 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 @@ -355,4 +355,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
<data name="ExcelMemberMayReturnNothingInspection" xml:space="preserve">
<value>A procedure that returns an object may return 'Nothing'. That will cause a runtime error 91 - "Object variable or With block variable not set" on subsequent member access. Perform an 'Is Nothing' check after the 'Set' assignment to guard against runtime errors.</value>
</data>
<data name="ExcelUdfNameIsValidCellReferenceInspection" xml:space="preserve">
<value>Functions that are visible to Excel as User-Defined Functions will return a '#REF' error when used on a Worksheet if they match the name of a valid cell reference. If the function is intended to be used as a UDF, it must be renamed. If the function is not intended to be used as a UDF, it should be scoped as 'Private' or moved out of a standard Module.</value>
</data>
</root>
9 changes: 9 additions & 0 deletions Rubberduck.Resources/Inspections/InspectionNames.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/InspectionNames.resx
Expand Up @@ -354,4 +354,7 @@
<data name="ExcelMemberMayReturnNothingInspection" xml:space="preserve">
<value>Member access may return 'Nothing'</value>
</data>
<data name="ExcelUdfNameIsValidCellReferenceInspection" xml:space="preserve">
<value>Function is hidden by Excel cell reference</value>
</data>
</root>

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 @@ -385,4 +385,8 @@
<value>Result of '{0}' call is not tested for 'Nothing'.</value>
<comment>{0} Member identifier</comment>
</data>
<data name="ExcelUdfNameIsValidCellReferenceInspection" xml:space="preserve">
<value>'{0}' is hidden by a valid Excel cell reference.</value>
<comment>{0} Function name</comment>
</data>
</root>
9 changes: 9 additions & 0 deletions Rubberduck.Resources/Settings/AutoCompletesPage.Designer.cs

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

@@ -0,0 +1,128 @@
using System.Linq;
using System.Threading;
using NUnit.Framework;
using Rubberduck.Inspections.Inspections.Concrete;
using Rubberduck.VBEditor.SafeComWrappers;
using RubberduckTests.Mocks;

namespace RubberduckTests.Inspections
{
[TestFixture]
public class ExcelUdfNameIsValidCellReferenceInspectionTests
{
[TestCase("a1")]
[TestCase("A1")]
[TestCase("AA1")]
[TestCase("ZZ1")]
[TestCase("XFD1")]
[TestCase("XEZ1")]
[TestCase("WZZ1")]
[TestCase("Foo42")]
[TestCase("XFD1048576")]
[Category("Inspections")]
public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsResult_ValidCells(string identifier)
{
const string codeTemplate =
@"Public Function {0}() As Long
{0} = 42
End Function
";

Assert.AreEqual(1, InspectionResultCount(string.Format(codeTemplate, identifier), ComponentType.StandardModule));
}

[TestCase("Foo")]
[TestCase("XXX69")]
[TestCase("XKCD42")]
[TestCase("AAA1234567")]
[Category("Inspections")]
public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsNoResult_InvalidAsCell(string identifier)
{
const string codeTemplate =
@"Public Function {0}() As Long
{0} = 42
End Function
";

Assert.AreEqual(0, InspectionResultCount(string.Format(codeTemplate, identifier), ComponentType.StandardModule));
}

[TestCase(ComponentType.ClassModule)]
[TestCase(ComponentType.UserForm)]
[TestCase(ComponentType.DocObject)]
[Category("Inspections")]
public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsNoResult_NonStandardModule(ComponentType moduleType)
{
const string code =
@"Public Function A1() As Long
A1 = 42
End Function
";

Assert.AreEqual(0, InspectionResultCount(code, moduleType));
}

[Test]
[Category("Inspections")]
public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsNoResult_Ignored()
{
const string code =
@"'@Ignore ExcelUdfNameIsValidCellReference
Public Function A1() As Long
A1 = 42
End Function
";

Assert.AreEqual(0, InspectionResultCount(code, ComponentType.StandardModule));
}

[Test]
[Category("Inspections")]
public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsNoResult_PrivateFunction()
{
const string code =
@"Private Function A1() As Long
A1 = 42
End Function
";

Assert.AreEqual(0, InspectionResultCount(code, ComponentType.StandardModule));
}

[TestCase("Sub A1()", "Sub")]
[TestCase("Property Get A1() As Long", "Property")]
[TestCase("Property Let A1(foo As Long)", "Property")]
[TestCase("Property Set A1(foo As Variant)", "Property")]
[Category("Inspections")]
public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsNoResult_NonFunction(string signature, string ending)
{
const string codeTemplate =
@"{0}
A1 = 42
End {1}
";

Assert.AreEqual(0, InspectionResultCount(string.Format(codeTemplate, signature, ending), ComponentType.StandardModule));
}

private static int InspectionResultCount(string inputCode, ComponentType moduleType)
{
var builder = new MockVbeBuilder();
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
.AddComponent("UnderTest", moduleType, inputCode)
.AddReference("Excel", MockVbeBuilder.LibraryPathMsExcel, 1, 8, true)
.Build();

var vbe = builder.AddProject(project).Build();

using (var state = MockParser.CreateAndParse(vbe.Object))
{

var inspection = new ExcelUdfNameIsValidCellReferenceInspection(state);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

return inspectionResults.Count();
}
}
}
}

0 comments on commit fb0f9b7

Please sign in to comment.