Skip to content

Commit 9df2566

Browse files
authored
Merge pull request #6035 from BZngr/5730PublicShouldBePrivate
Introduce PublicImplementationShouldBePrivate Inspection
2 parents 9168dbf + 6451f99 commit 9df2566

8 files changed

+332
-10
lines changed
Lines changed: 155 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,155 @@
1+
using Rubberduck.CodeAnalysis.CodeMetrics;
2+
using Rubberduck.CodeAnalysis.Inspections.Abstract;
3+
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.Parsing.VBA.DeclarationCaching;
6+
using Rubberduck.Refactorings.Common;
7+
using Rubberduck.Resources.Inspections;
8+
using Rubberduck.VBEditor;
9+
using System;
10+
using System.Collections.Generic;
11+
using System.Linq;
12+
using System.Text;
13+
using System.Threading.Tasks;
14+
15+
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
16+
{
17+
/// <summary>
18+
/// Flags Interface implementation members and EventHandlers with Public scope.
19+
/// </summary>
20+
/// <why>
21+
/// The default (Public) interface of a class module should not expose the implementation of other interfaces or event handler procedures.
22+
/// If the implementation of an interface member or event handler is useful for a class to expose, it should do so using
23+
/// a dedicated Public member rather than changing the interface member or event handler scope from 'Private' to 'Public'.
24+
/// </why>
25+
/// <example hasResult="true">
26+
/// <module name="MyClassModule" type="Class Module">
27+
/// <![CDATA[
28+
/// Implements ISomething 'ISomething defines procedure "DoSomething"
29+
///
30+
/// Public Sub ISomething_DoSomething(ByVal someValue As Long)
31+
/// Debug.Print someValue
32+
/// End Sub
33+
/// ]]>
34+
/// </module>
35+
/// </example>
36+
/// <example hasResult="true">
37+
/// <module name="MyClassModule" type="Class Module">
38+
/// <![CDATA[
39+
/// Private WithEvents abc As MyEvent 'MyEvent defines a "MyValueChanged" event
40+
///
41+
/// Public Sub abc_MyValueChanged(ByVal newVal As Long)
42+
/// Debug.Print newVal
43+
/// End Sub
44+
/// ]]>
45+
/// </module>
46+
/// </example>
47+
/// <example hasResult="true">
48+
/// <module name="MyClassModule" type="Class Module">
49+
/// <![CDATA[
50+
/// 'Code found in the "ThisWorkbook" Document
51+
/// Public Sub Workbook_Open()
52+
/// Debug.Print "Workbook was opened"
53+
/// End Sub
54+
/// ]]>
55+
/// </module>
56+
/// </example>
57+
/// <example hasResult="false">
58+
/// <module name="MyClassModule" type="Class Module">
59+
/// <![CDATA[
60+
/// Implements ISomething 'ISomething defines procedure "DoSomething"
61+
///
62+
/// Private Sub ISomething_DoSomething(ByVal someValue As Long)
63+
/// Debug.Print someValue
64+
/// End Sub
65+
/// ]]>
66+
/// </module>
67+
/// </example>
68+
/// <example hasResult="false">
69+
/// <module name="MyClassModule" type="Class Module">
70+
/// <![CDATA[
71+
/// Public Sub Do_Something(ByVal someValue As Long)
72+
/// Debug.Print someValue
73+
/// End Sub
74+
/// ]]>
75+
/// </module>
76+
77+
internal sealed class PublicImplementationShouldBePrivateInspection : DeclarationInspectionBase
78+
{
79+
public PublicImplementationShouldBePrivateInspection(IDeclarationFinderProvider declarationFinderProvider)
80+
: base(declarationFinderProvider, DeclarationType.Member)
81+
{}
82+
83+
//Overriding DoGetInspectionResults in order to dereference the DeclarationFinder FindXXX declaration
84+
//lists only once per inspections pass.
85+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults(DeclarationFinder finder)
86+
{
87+
var publicMembers = finder.UserDeclarations(DeclarationType.Member)
88+
.Where(d => !d.HasPrivateAccessibility()
89+
&& IsLikeAnImplementerOrHandlerName(d.IdentifierName));
90+
91+
if (!publicMembers.Any())
92+
{
93+
return Enumerable.Empty<IInspectionResult>();
94+
}
95+
96+
var publicImplementersAndHandlers = finder.FindAllInterfaceImplementingMembers()
97+
.Where(d => !d.HasPrivateAccessibility())
98+
.Concat(finder.FindEventHandlers()
99+
.Where(d => !d.HasPrivateAccessibility()));
100+
101+
var publicDocumentEvents = FindDocumentEventHandlers(publicMembers);
102+
103+
return publicMembers.Intersect(publicImplementersAndHandlers)
104+
.Concat(publicDocumentEvents)
105+
.Select(InspectionResult)
106+
.ToList();
107+
}
108+
109+
private static IEnumerable<Declaration> FindDocumentEventHandlers(IEnumerable<Declaration> publicMembers)
110+
{
111+
//Excel and Word
112+
var docEventPrefixes = new List<string>()
113+
{
114+
"Workbook",
115+
"Worksheet",
116+
"Document"
117+
};
118+
119+
//FindDocumentEventHandlers can be a source of False Positives if a Document's code
120+
//contains Public procedure Identifiers (with a single underscore).
121+
return publicMembers.Where(d => d.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Document)
122+
&& d.DeclarationType.Equals(DeclarationType.Procedure)
123+
&& docEventPrefixes.Any(dep => IsLikeADocumentEventHandlerName(d.IdentifierName, dep)));
124+
}
125+
126+
protected override string ResultDescription(Declaration declaration)
127+
{
128+
return string.Format(Resources.Inspections.InspectionResults.PublicImplementationShouldBePrivateInspection,
129+
declaration.IdentifierName);
130+
}
131+
132+
private static bool IsLikeAnImplementerOrHandlerName(string identifier)
133+
{
134+
var splitup = identifier.Split('_');
135+
return splitup.Length == 2 && splitup[1].Length > 0;
136+
}
137+
138+
private static bool IsLikeADocumentEventHandlerName(string procedureName, string docEventHandlerPrefix)
139+
{
140+
var splitup = procedureName.Split('_');
141+
142+
return splitup.Length == 2
143+
&& splitup[0].Equals(docEventHandlerPrefix, StringComparison.InvariantCultureIgnoreCase)
144+
&& splitup[1].Length > 2 //Excel and Word document events all have at least 3 characters
145+
&& !splitup[1].Any(c => char.IsDigit(c)); //Excel and Word document event names do not contain numbers
146+
}
147+
148+
//The 'DoGetInspectionResults' override excludes IsResultDeclaration from the execution path
149+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
150+
{
151+
throw new NotImplementedException();
152+
}
153+
154+
}
155+
}

Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs

Lines changed: 9 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Resources/Inspections/InspectionInfo.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -475,4 +475,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
475475
<data name="UDTMemberNotUsedInspection" xml:space="preserve">
476476
<value>A User Defined Type (UDT) member is declared but not used. Consider removing the UDT member declaration.</value>
477477
</data>
478+
<data name="PublicImplementationShouldBePrivateInspection" xml:space="preserve">
479+
<value>The default (Public) interface of a class module should not expose the implementation of other interfaces or event handler procedures.</value>
480+
</data>
478481
</root>

Rubberduck.Resources/Inspections/InspectionNames.Designer.cs

Lines changed: 9 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Resources/Inspections/InspectionNames.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -475,4 +475,7 @@
475475
<data name="UDTMemberNotUsedInspection" xml:space="preserve">
476476
<value>User Defined Type member is not used</value>
477477
</data>
478+
<data name="PublicImplementationShouldBePrivateInspection" xml:space="preserve">
479+
<value>Implementations of interfaces and event handlers should be Private</value>
480+
</data>
478481
</root>

Rubberduck.Resources/Inspections/InspectionResults.Designer.cs

Lines changed: 10 additions & 10 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Resources/Inspections/InspectionResults.resx

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -556,4 +556,8 @@ In memoriam, 1972-2018</value>
556556
<value>Control '{0}.{1}' is being accessed from outside its parent form.</value>
557557
<comment>{0} parent UserForm name; {1} control name</comment>
558558
</data>
559+
<data name="PublicImplementationShouldBePrivateInspection" xml:space="preserve">
560+
<value>Member '{0}' should be Private</value>
561+
<comment>{0} Member Identifier</comment>
562+
</data>
559563
</root>
Lines changed: 139 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,139 @@
1+
using NUnit.Framework;
2+
using Rubberduck.CodeAnalysis.Inspections;
3+
using Rubberduck.CodeAnalysis.Inspections.Concrete;
4+
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.VBEditor.SafeComWrappers;
6+
using RubberduckTests.Mocks;
7+
using System;
8+
using System.Collections.Generic;
9+
using System.Linq;
10+
using System.Text;
11+
using System.Threading.Tasks;
12+
13+
namespace RubberduckTests.Inspections
14+
{
15+
[TestFixture]
16+
public class PublicImplementationShouldBePrivateInspectionTests : InspectionTestsBase
17+
{
18+
[TestCase("Class_Initialize", "Private", 0)]
19+
[TestCase("Class_Initialize", "Public", 1)]
20+
[TestCase("Class_Terminate", "Friend", 1)]
21+
[TestCase("Class_NamedPoorly", "Friend", 0)]
22+
[TestCase("Class_Initialize_Again", "Friend", 0)]
23+
[Category("Inspections")]
24+
[Category(nameof(PublicImplementationShouldBePrivateInspectionTests))]
25+
public void LifecycleHandlers(string memberIdentifier, string accessibility, long expected)
26+
{
27+
var inputCode =
28+
$@"Option Explicit
29+
30+
Private mVal As Long
31+
32+
{accessibility} Sub {memberIdentifier}()
33+
mVal = 5
34+
End Sub
35+
";
36+
37+
var inspectionResults = InspectionResultsForModules(
38+
(MockVbeBuilder.TestModuleName, inputCode, ComponentType.ClassModule)); ;
39+
40+
var actual = inspectionResults.Count();
41+
42+
Assert.AreEqual(expected, actual);
43+
}
44+
45+
[TestCase("Public", 1)]
46+
[TestCase("Private", 0)]
47+
[Category("Inspections")]
48+
[Category(nameof(PublicImplementationShouldBePrivateInspectionTests))]
49+
public void UserDefinedEventHandlers(string accessibility, long expected)
50+
{
51+
var eventDeclaringClassName = "EventClass";
52+
var eventDeclarationCode =
53+
$@"
54+
Option Explicit
55+
56+
Public Event MyEvent(ByVal arg1 As Integer, ByVal arg2 As String)
57+
";
58+
59+
var inputCode =
60+
$@"
61+
Option Explicit
62+
63+
Private WithEvents abc As {eventDeclaringClassName}
64+
65+
{accessibility} Sub abc_MyEvent(ByVal i As Integer, ByVal s As String)
66+
End Sub
67+
";
68+
69+
var inspectionResults = InspectionResultsForModules(
70+
(eventDeclaringClassName, eventDeclarationCode, ComponentType.ClassModule),
71+
(MockVbeBuilder.TestModuleName, inputCode, ComponentType.ClassModule));
72+
73+
var actual = inspectionResults.Count();
74+
75+
Assert.AreEqual(expected, actual);
76+
}
77+
78+
[TestCase("Public", 1)]
79+
[TestCase("Private", 0)]
80+
[Category("Inspections")]
81+
[Category(nameof(PublicImplementationShouldBePrivateInspectionTests))]
82+
public void InterfaceImplementingMembers(string accessibility, long expected)
83+
{
84+
var interfaceDeclarationClass = "ITestClass";
85+
var interfaceDeclarationCode =
86+
$@"
87+
Option Explicit
88+
89+
Public Sub ImplementMe(ByVal arg1 As Integer, ByVal arg2 As String)
90+
End Sub
91+
";
92+
93+
var inputCode =
94+
$@"
95+
Option Explicit
96+
97+
Implements {interfaceDeclarationClass}
98+
99+
{accessibility} Sub {interfaceDeclarationClass}_ImplementMe(ByVal i As Integer, ByVal s As String)
100+
End Sub
101+
";
102+
103+
var inspectionResults = InspectionResultsForModules(
104+
(interfaceDeclarationClass, interfaceDeclarationCode, ComponentType.ClassModule),
105+
(MockVbeBuilder.TestModuleName, inputCode, ComponentType.ClassModule));
106+
107+
var actual = inspectionResults.Count();
108+
109+
Assert.AreEqual(expected, actual);
110+
}
111+
112+
[TestCase("Workbook_Open", "ThisWorkbook", 1)]
113+
[TestCase("Worksheet_SelectionChange", "Sheet1", 1)]
114+
[TestCase("Document_Open", "ThisDocument", 1)]
115+
[TestCase("Document_Open_Again", "ThisDocument", 0)]
116+
[Category("Inspections")]
117+
[Category(nameof(PublicImplementationShouldBePrivateInspectionTests))]
118+
public void DocumentEventHandlers(string subroutineName, string objectName, long expected)
119+
{
120+
var inputCode =
121+
$@"
122+
Public Sub {subroutineName}()
123+
Range(""A1"").Value = ""Test""
124+
End Sub";
125+
126+
var inspectionResults = InspectionResultsForModules(
127+
(objectName, inputCode, ComponentType.Document)); ;
128+
129+
var actual = inspectionResults.Count();
130+
131+
Assert.AreEqual(expected, actual);
132+
}
133+
134+
protected override IInspection InspectionUnderTest(RubberduckParserState state)
135+
{
136+
return new PublicImplementationShouldBePrivateInspection(state);
137+
}
138+
}
139+
}

0 commit comments

Comments
 (0)