Skip to content

Commit 21bbebd

Browse files
committed
Stop reporting functions potentially conflicting as Udfs in private modules
Also makes some more declaration inspections use the base classes.
1 parent fa57ae7 commit 21bbebd

File tree

4 files changed

+121
-65
lines changed

4 files changed

+121
-65
lines changed

Rubberduck.CodeAnalysis/Inspections/Abstract/DeclarationInspectionBaseBase.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4848
return results;
4949
}
5050

51-
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
51+
protected virtual IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
5252
{
5353
var finder = DeclarationFinderProvider.DeclarationFinder;
5454
return DoGetInspectionResults(module, finder);

Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ExcelUdfNameIsValidCellReferenceInspection.cs

Lines changed: 67 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -3,12 +3,14 @@
33
using System.Linq;
44
using System.Text.RegularExpressions;
55
using Rubberduck.Inspections.Abstract;
6-
using Rubberduck.Inspections.Results;
76
using Rubberduck.Parsing.Inspections;
87
using Rubberduck.Parsing.Inspections.Abstract;
98
using Rubberduck.Parsing.Symbols;
109
using Rubberduck.Parsing.VBA;
10+
using Rubberduck.Parsing.VBA.DeclarationCaching;
1111
using Rubberduck.Resources.Inspections;
12+
using Rubberduck.VBEditor;
13+
using Rubberduck.VBEditor.SafeComWrappers;
1214

1315
namespace Rubberduck.Inspections.Inspections.Concrete
1416
{
@@ -33,9 +35,69 @@ namespace Rubberduck.Inspections.Inspections.Concrete
3335
/// ]]>
3436
/// </example>
3537
[RequiredLibrary("Excel")]
36-
public class ExcelUdfNameIsValidCellReferenceInspection : InspectionBase
38+
public class ExcelUdfNameIsValidCellReferenceInspection : DeclarationInspectionBase
3739
{
38-
public ExcelUdfNameIsValidCellReferenceInspection(RubberduckParserState state) : base(state) { }
40+
public ExcelUdfNameIsValidCellReferenceInspection(RubberduckParserState state)
41+
: base(state, new []{DeclarationType.Function}, new []{DeclarationType.PropertyGet, DeclarationType.LibraryFunction})
42+
{ }
43+
44+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
45+
{
46+
if (!State.DeclarationFinder.Projects.Any(project => !project.IsUserDefined
47+
&& project.IdentifierName == "Excel"))
48+
{
49+
return Enumerable.Empty<IInspectionResult>();
50+
}
51+
52+
return base.DoGetInspectionResults();
53+
}
54+
55+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
56+
{
57+
if (!State.DeclarationFinder.Projects.Any(project => !project.IsUserDefined
58+
&& project.IdentifierName == "Excel"))
59+
{
60+
return Enumerable.Empty<IInspectionResult>();
61+
}
62+
63+
return base.DoGetInspectionResults(module);
64+
}
65+
66+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
67+
{
68+
if (module.ComponentType != ComponentType.StandardModule)
69+
{
70+
return Enumerable.Empty<IInspectionResult>();
71+
}
72+
73+
var proceduralModuleDeclaration = finder.Members(module, DeclarationType.ProceduralModule)
74+
.SingleOrDefault() as ProceduralModuleDeclaration;
75+
76+
if (proceduralModuleDeclaration == null
77+
|| proceduralModuleDeclaration.IsPrivateModule)
78+
{
79+
return Enumerable.Empty<IInspectionResult>();
80+
}
81+
82+
return base.DoGetInspectionResults(module, finder);
83+
}
84+
85+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
86+
{
87+
if (!VisibleAsUdf.Contains(declaration.Accessibility))
88+
{
89+
return false;
90+
}
91+
92+
var cellIdMatch = ValidCellIdRegex.Match(declaration.IdentifierName);
93+
if (!cellIdMatch.Success)
94+
{
95+
return false;
96+
}
97+
98+
var row = Convert.ToUInt32(cellIdMatch.Groups["Row"].Value);
99+
return row > 0 && row <= MaximumExcelRows;
100+
}
39101

40102
private static readonly Regex ValidCellIdRegex =
41103
new Regex(@"^([a-z]|[a-z]{2}|[a-w][a-z]{2}|x([a-e][a-z]|f[a-d]))(?<Row>\d+)$",
@@ -45,25 +107,9 @@ public ExcelUdfNameIsValidCellReferenceInspection(RubberduckParserState state) :
45107

46108
private const uint MaximumExcelRows = 1048576;
47109

48-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
110+
protected override string ResultDescription(Declaration declaration)
49111
{
50-
var excel = State.DeclarationFinder.Projects.SingleOrDefault(item => !item.IsUserDefined && item.IdentifierName == "Excel");
51-
if (excel == null)
52-
{
53-
return Enumerable.Empty<IInspectionResult>();
54-
}
55-
56-
var candidates = UserDeclarations.OfType<FunctionDeclaration>().Where(decl =>
57-
decl.ParentScopeDeclaration.DeclarationType == DeclarationType.ProceduralModule &&
58-
VisibleAsUdf.Contains(decl.Accessibility));
59-
60-
return (from function in candidates.Where(decl => ValidCellIdRegex.IsMatch(decl.IdentifierName))
61-
let row = Convert.ToUInt32(ValidCellIdRegex.Matches(function.IdentifierName)[0].Groups["Row"].Value)
62-
where row > 0 && row <= MaximumExcelRows
63-
select new DeclarationInspectionResult(this,
64-
string.Format(InspectionResults.ExcelUdfNameIsValidCellReferenceInspection, function.IdentifierName),
65-
function))
66-
.Cast<IInspectionResult>().ToList();
112+
return string.Format(InspectionResults.ExcelUdfNameIsValidCellReferenceInspection, declaration.IdentifierName);
67113
}
68114
}
69115
}
Lines changed: 39 additions & 43 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,9 @@
1-
using System.Collections.Generic;
2-
using System.Linq;
1+
using System.Linq;
32
using Rubberduck.Inspections.Abstract;
4-
using Rubberduck.Inspections.Results;
5-
using Rubberduck.Parsing.Inspections.Abstract;
63
using Rubberduck.Resources.Inspections;
74
using Rubberduck.Parsing.Symbols;
85
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.Parsing.VBA.DeclarationCaching;
97

108
namespace Rubberduck.Inspections.Concrete
119
{
@@ -38,58 +36,56 @@ namespace Rubberduck.Inspections.Concrete
3836
/// End Sub
3937
/// ]]>
4038
/// </example>
41-
public sealed class MoveFieldCloserToUsageInspection : InspectionBase
39+
public sealed class MoveFieldCloserToUsageInspection : DeclarationInspectionBase
4240
{
4341
public MoveFieldCloserToUsageInspection(RubberduckParserState state)
44-
: base(state) { }
42+
: base(state, DeclarationType.Variable)
43+
{}
4544

46-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
45+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
4746
{
48-
return State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
49-
.Where(declaration =>
50-
{
51-
if (declaration.IsWithEvents
52-
|| !new[] {DeclarationType.ClassModule, DeclarationType.Document, DeclarationType.ProceduralModule}.Contains(declaration.ParentDeclaration.DeclarationType))
53-
{
54-
return false;
55-
}
47+
if (declaration.IsWithEvents
48+
|| !IsField(declaration))
49+
{
50+
return false;
51+
}
5652

57-
var asType = declaration.AsTypeDeclaration;
58-
if (asType != null && asType.ProjectName.Equals("Rubberduck") &&
59-
(asType.IdentifierName.Equals("PermissiveAssertClass") || asType.IdentifierName.Equals("AssertClass")))
60-
{
61-
return false;
62-
}
53+
if (IsRubberduckAssertField(declaration))
54+
{
55+
return false;
56+
}
6357

64-
var firstReference = declaration.References.FirstOrDefault();
58+
var firstReference = declaration.References.FirstOrDefault();
59+
var usageMember = firstReference?.ParentScoping;
6560

66-
if (firstReference == null ||
67-
declaration.References.Any(r => r.ParentScoping != firstReference.ParentScoping))
68-
{
69-
return false;
70-
}
61+
if (usageMember == null
62+
|| declaration.References.Any(reference => !reference.ParentScoping.Equals(usageMember)))
63+
{
64+
return false;
65+
}
7166

72-
var parentDeclaration = ParentDeclaration(firstReference);
67+
return usageMember.DeclarationType == DeclarationType.Procedure
68+
|| usageMember.DeclarationType == DeclarationType.Function;
69+
}
7370

74-
return parentDeclaration != null &&
75-
!new[]
76-
{
77-
DeclarationType.PropertyGet,
78-
DeclarationType.PropertyLet,
79-
DeclarationType.PropertySet
80-
}.Contains(parentDeclaration.DeclarationType);
81-
})
82-
.Select(issue =>
83-
new DeclarationInspectionResult(this, string.Format(InspectionResults.MoveFieldCloserToUsageInspection, issue.IdentifierName), issue));
71+
private static bool IsField(Declaration variableDeclaration)
72+
{
73+
var parentDeclarationType = variableDeclaration.ParentDeclaration.DeclarationType;
74+
return parentDeclarationType.HasFlag(DeclarationType.Module);
8475
}
8576

86-
private Declaration ParentDeclaration(IdentifierReference reference)
77+
private static bool IsRubberduckAssertField(Declaration fieldDeclaration)
8778
{
88-
var declarationTypes = new[] {DeclarationType.Function, DeclarationType.Procedure, DeclarationType.Property};
79+
var asType = fieldDeclaration.AsTypeDeclaration;
80+
return asType != null
81+
&& asType.ProjectName.Equals("Rubberduck")
82+
&& (asType.IdentifierName.Equals("PermissiveAssertClass")
83+
|| asType.IdentifierName.Equals("AssertClass"));
84+
}
8985

90-
return UserDeclarations.SingleOrDefault(d =>
91-
reference.ParentScoping.Equals(d) && declarationTypes.Contains(d.DeclarationType) &&
92-
d.QualifiedName.QualifiedModuleName.Equals(reference.QualifiedModuleName));
86+
protected override string ResultDescription(Declaration declaration)
87+
{
88+
return string.Format(InspectionResults.MoveFieldCloserToUsageInspection, declaration.IdentifierName);
9389
}
9490
}
9591
}

RubberduckTests/Inspections/ExcelUdfNameIsValidCellReferenceInspectionTests.cs

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,20 @@ End Function
3232
Assert.AreEqual(1, InspectionResultCount(string.Format(codeTemplate, identifier), ComponentType.StandardModule));
3333
}
3434

35+
[Test]
36+
[Category("Inspections")]
37+
public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsResult_ValidCellsInPrivateModule()
38+
{
39+
const string code =
40+
@"Option Private Module
41+
Public Function A1() As Long
42+
A1 = 42
43+
End Function
44+
";
45+
46+
Assert.AreEqual(0, InspectionResultCount(code, ComponentType.StandardModule));
47+
}
48+
3549
[TestCase("Foo")]
3650
[TestCase("XXX69")]
3751
[TestCase("XKCD42")]

0 commit comments

Comments
 (0)