Skip to content

Commit

Permalink
Add new inspection for Excel UDFs hidden by cells.
Browse files Browse the repository at this point in the history
  • Loading branch information
comintern committed Nov 3, 2018
1 parent 0aaf7c1 commit 0b93e50
Show file tree
Hide file tree
Showing 14 changed files with 279 additions and 179 deletions.
Original file line number Diff line number Diff line change
@@ -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();
}
}
}
Original file line number Diff line number Diff line change
@@ -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.VBA;
Expand All @@ -18,7 +19,10 @@ public sealed class RenameDeclarationQuickFix : QuickFixBase
private readonly IMessageBox _messageBox;

public RenameDeclarationQuickFix(IVBE vbe, RubberduckParserState state, IMessageBox messageBox)
: base(typeof(HungarianNotationInspection), typeof(UseMeaningfulNameInspection), typeof(DefaultProjectNameInspection))
: base(typeof(HungarianNotationInspection),
typeof(UseMeaningfulNameInspection),
typeof(DefaultProjectNameInspection),
typeof(ExcelUdfNameIsValidCellReferenceInspection))
{
_vbe = vbe;
_state = state;
Expand Down
27 changes: 7 additions & 20 deletions Rubberduck.Core/Properties/Settings.settings
Original file line number Diff line number Diff line change
Expand Up @@ -268,26 +268,13 @@
</Setting>
<Setting Name="AutoCompleteSettings" Type="Rubberduck.Settings.AutoCompleteSettings" Scope="Application">
<Value Profile="(Default)">&lt;?xml version="1.0" encoding="utf-16"?&gt;
&lt;AutoCompleteSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema" IsEnabled="false" CompleteBlockOnTab="true" CompleteBlockOnEnter="true" EnableSmartConcat="true"&gt;
&lt;AutoCompletes&gt;
&lt;AutoComplete Key="AutoCompleteClosingBrace" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteClosingBracket" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteClosingParenthese" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteClosingString" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteDoBlock" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteEnumBlock" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteForBlock" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteFunctionBlock" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteIfBlock" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteOnErrorResumeNextBlock" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompletePrecompilerIfBlock" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompletePropertyBlock" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteSelectBlock" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteSubBlock" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteTypeBlock" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteWhileBlock" IsEnabled="true" /&gt;
&lt;AutoComplete Key="AutoCompleteWithBlock" IsEnabled="true" /&gt;
&lt;/AutoCompletes&gt;
&lt;AutoCompleteSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema" IsEnabled="false"&gt;
&lt;SmartConcat&gt;
&lt;IsEnabled&gt;false&lt;/IsEnabled&gt;
&lt;ConcatVbNewLineModifier&gt;None&lt;/ConcatVbNewLineModifier&gt;
&lt;/SmartConcat&gt;
&lt;SelfClosingPairs IsEnabled="false" /&gt;
&lt;BlockCompletion IsEnabled="false" CompleteOnEnter="false" CompleteOnTab="false" /&gt;
&lt;/AutoCompleteSettings&gt;</Value>
</Setting>
</Settings>
Expand Down
28 changes: 7 additions & 21 deletions Rubberduck.Core/app.config
Original file line number Diff line number Diff line change
Expand Up @@ -395,27 +395,13 @@
<setting name="AutoCompleteSettings" serializeAs="Xml">
<value>
<AutoCompleteSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance"
xmlns:xsd="http://www.w3.org/2001/XMLSchema" IsEnabled="false"
CompleteBlockOnTab="true" CompleteBlockOnEnter="true" EnableSmartConcat="true">
<AutoCompletes>
<AutoComplete Key="AutoCompleteClosingBrace" IsEnabled="true" />
<AutoComplete Key="AutoCompleteClosingBracket" IsEnabled="true" />
<AutoComplete Key="AutoCompleteClosingParenthese" IsEnabled="true" />
<AutoComplete Key="AutoCompleteClosingString" IsEnabled="true" />
<AutoComplete Key="AutoCompleteDoBlock" IsEnabled="true" />
<AutoComplete Key="AutoCompleteEnumBlock" IsEnabled="true" />
<AutoComplete Key="AutoCompleteForBlock" IsEnabled="true" />
<AutoComplete Key="AutoCompleteFunctionBlock" IsEnabled="true" />
<AutoComplete Key="AutoCompleteIfBlock" IsEnabled="true" />
<AutoComplete Key="AutoCompleteOnErrorResumeNextBlock" IsEnabled="true" />
<AutoComplete Key="AutoCompletePrecompilerIfBlock" IsEnabled="true" />
<AutoComplete Key="AutoCompletePropertyBlock" IsEnabled="true" />
<AutoComplete Key="AutoCompleteSelectBlock" IsEnabled="true" />
<AutoComplete Key="AutoCompleteSubBlock" IsEnabled="true" />
<AutoComplete Key="AutoCompleteTypeBlock" IsEnabled="true" />
<AutoComplete Key="AutoCompleteWhileBlock" IsEnabled="true" />
<AutoComplete Key="AutoCompleteWithBlock" IsEnabled="true" />
</AutoCompletes>
xmlns:xsd="http://www.w3.org/2001/XMLSchema" IsEnabled="false">
<SmartConcat>
<IsEnabled>false</IsEnabled>
<ConcatVbNewLineModifier>None</ConcatVbNewLineModifier>
</SmartConcat>
<SelfClosingPairs IsEnabled="false" />
<BlockCompletion IsEnabled="false" CompleteOnEnter="false" CompleteOnTab="false" />
</AutoCompleteSettings>
</value>
</setting>
Expand Down
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
Original file line number Diff line number Diff line change
Expand Up @@ -349,4 +349,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
<data name="AssignmentNotUsedInspection" xml:space="preserve">
<value>An assignment is immediately overridden by another assignment or is never referenced.</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
Original file line number Diff line number Diff line change
Expand Up @@ -348,4 +348,7 @@
<data name="AssignmentNotUsedInspection" xml:space="preserve">
<value>Assignment is not used</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
Original file line number Diff line number Diff line change
Expand Up @@ -378,4 +378,8 @@
<data name="AssignmentNotUsedInspection" xml:space="preserve">
<value>An assignment is immediately overridden by another assignment or is never referenced.</value>
</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>
16 changes: 12 additions & 4 deletions Rubberduck.Resources/Rubberduck.Resources.csproj
Original file line number Diff line number Diff line change
Expand Up @@ -12,12 +12,20 @@
<Resource Include="**\*.png" />
<Resource Include="**\*.bmp" />
<Resource Include="**\*.txt" />
<Resource Update="**\*.resx">
<Generator>PublicResXFileCodeGenerator</Generator>
<LastGenOutput>$([System.String]::Copy('%(FileName)')).Designer.cs</LastGenOutput>
</Resource>
</ItemGroup>

<ItemGroup>
<Compile Update="**\*.Designer.cs">
<DesignTime>True</DesignTime>
<AutoGen>True</AutoGen>
<DependentUpon>$([System.String]::Copy('%(Filename)').Replace('.Designer', '')).resx</DependentUpon>
</Compile>
</ItemGroup>

<ItemGroup>
<EmbeddedResource Update="**\*.resx">
<Generator>PublicResXFileCodeGenerator</Generator>
<LastGenOutput>$([System.String]::Copy('%(FileName)')).Designer.cs</LastGenOutput>
</EmbeddedResource>
</ItemGroup>
</Project>
Loading

0 comments on commit 0b93e50

Please sign in to comment.