Skip to content

Commit 966b43a

Browse files
authored
Merge branch 'next' into 5803_MissingSetter
2 parents 9009181 + 8d90008 commit 966b43a

File tree

11 files changed

+318
-0
lines changed

11 files changed

+318
-0
lines changed
Lines changed: 99 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,99 @@
1+
using Rubberduck.CodeAnalysis.Inspections.Abstract;
2+
using Rubberduck.Parsing;
3+
using Rubberduck.Parsing.Grammar;
4+
using Rubberduck.Parsing.Symbols;
5+
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.Parsing.VBA.DeclarationCaching;
7+
using Rubberduck.Resources.Inspections;
8+
using Tokens = Rubberduck.Resources.Tokens;
9+
10+
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
11+
{
12+
/// <summary>
13+
/// This inspection warns about references to the default instance of a class, inside that class.
14+
/// </summary>
15+
/// <why>
16+
/// While a stateful default instance might be intentional, when it isn't it's easily a source of bugs.
17+
/// Use the Me qualifier to explicitly refer to the current instance and eliminate any ambiguity.
18+
/// Global state accidentally stored in a class' default instance is not shared by all other instances of that class.
19+
/// </why>
20+
/// <example hasResult="true">
21+
/// <module name="Module1" type="Standard Module">
22+
/// <![CDATA[
23+
/// Option Explicit
24+
///
25+
/// Public Sub Test1()
26+
/// UserForm1.Show ' the default instance is being shown
27+
/// End Sub
28+
///
29+
/// Public Sub Test2()
30+
/// With New UserForm1
31+
/// .Show ' a new instance is being shown
32+
/// End With
33+
/// End Sub
34+
/// ]]>
35+
/// </module>
36+
/// <module name="UserForm1" type="UserForm Module">
37+
/// <![CDATA[
38+
/// Option Explicit
39+
/// Private ClickCount As Long
40+
///
41+
/// Private Sub CommandButton1_Click()
42+
/// ClickCount = ClickCount + 1
43+
/// UserForm1.TextBox1.Text = ClickCount ' only TextBox1 on the default instance is affected
44+
/// End Sub
45+
/// ]]>
46+
/// </module>
47+
/// </example>
48+
/// <example hasResult="false">
49+
/// <module name="Module1" type="Standard Module">
50+
/// <![CDATA[
51+
/// Option Explicit
52+
///
53+
/// Public Sub Test1()
54+
/// UserForm1.Show ' the default instance is being shown
55+
/// End Sub
56+
///
57+
/// Public Sub Test2()
58+
/// With New UserForm1
59+
/// .Show ' a new instance is being shown
60+
/// End With
61+
/// End Sub
62+
/// ]]>
63+
/// </module>
64+
/// <module name="UserForm1" type="UserForm Module">
65+
/// <![CDATA[
66+
/// Option Explicit
67+
/// Private ClickCount As Long
68+
///
69+
/// Private Sub CommandButton1_Click()
70+
/// ClickCount = ClickCount + 1
71+
/// Me.TextBox1.Text = ClickCount ' always works as expected
72+
/// End Sub
73+
/// ]]>
74+
/// </module>
75+
/// </example>
76+
internal sealed class SuspiciousPredeclaredInstanceAccessInspection : IdentifierReferenceInspectionBase
77+
{
78+
public SuspiciousPredeclaredInstanceAccessInspection(IDeclarationFinderProvider declarationFinderProvider)
79+
: base(declarationFinderProvider)
80+
{
81+
}
82+
83+
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
84+
{
85+
return
86+
reference.Declaration is ClassModuleDeclaration module &&
87+
module.HasPredeclaredId &&
88+
reference.ParentScoping.ParentDeclaration.Equals(module) &&
89+
reference.Context.TryGetAncestor<VBAParser.MemberAccessExprContext>(out var expression) &&
90+
reference.IdentifierName != Tokens.Me && expression.lExpression()?.GetText() == reference.IdentifierName;
91+
}
92+
93+
protected override string ResultDescription(IdentifierReference reference)
94+
{
95+
reference.Context.TryGetAncestor<VBAParser.MemberAccessExprContext>(out var expression);
96+
return string.Format(InspectionResults.SuspiciousPredeclaredInstanceAccessInspection, reference.IdentifierName, expression.GetText());
97+
}
98+
}
99+
}
Lines changed: 67 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,67 @@
1+
using Rubberduck.CodeAnalysis.Inspections;
2+
using Rubberduck.CodeAnalysis.Inspections.Concrete;
3+
using Rubberduck.CodeAnalysis.QuickFixes.Abstract;
4+
using Rubberduck.Parsing.Rewriter;
5+
using Rubberduck.Resources;
6+
7+
namespace Rubberduck.CodeAnalysis.QuickFixes.Concrete
8+
{
9+
/// <summary>
10+
/// Replaces an explicit qualifier with 'Me'.
11+
/// </summary>
12+
/// <inspections>
13+
/// <inspection name="SuspiciousPredeclaredInstanceAccessInspection" />
14+
/// </inspections>
15+
/// <canfix multiple="true" procedure="true" module="true" project="true" all="true" />
16+
/// <example>
17+
/// <before>
18+
/// <![CDATA[
19+
/// Option Explicit
20+
/// Private ClickCount As Long
21+
///
22+
/// Private Sub CommandButton1_Click()
23+
/// ClickCount = ClickCount + 1
24+
/// ' works fine as long as the current instance is the default instance
25+
/// UserForm1.TextBox1.Text = ClickCount
26+
/// End Sub
27+
/// ]]>
28+
/// </before>
29+
/// <after>
30+
/// <![CDATA[
31+
/// Option Explicit
32+
/// Private ClickCount As Long
33+
///
34+
/// Private Sub CommandButton1_Click()
35+
/// ClickCount = ClickCount + 1
36+
/// ' works fine regardless of which instance we're in
37+
/// Me.TextBox1.Text = ClickCount
38+
/// End Sub
39+
/// ]]>
40+
/// </after>
41+
/// </example>
42+
internal class ReplaceQualifierWithMeQuickFix : QuickFixBase
43+
{
44+
public ReplaceQualifierWithMeQuickFix()
45+
:base(typeof(SuspiciousPredeclaredInstanceAccessInspection))
46+
{}
47+
48+
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
49+
{
50+
var rewriter = rewriteSession.CheckOutModuleRewriter(result.QualifiedSelection.QualifiedName);
51+
52+
var context = result.Context;
53+
rewriter.Replace(context.Start, Tokens.Me);
54+
}
55+
56+
public override string Description(IInspectionResult result)
57+
{
58+
return Resources.Inspections.QuickFixes.ReplaceQualifierWithMeQuickFix;
59+
}
60+
61+
public override bool CanFixMultiple => true;
62+
public override bool CanFixInProcedure => true;
63+
public override bool CanFixInModule => true;
64+
public override bool CanFixInProject => true;
65+
public override bool CanFixAll => true;
66+
}
67+
}

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
@@ -460,4 +460,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
460460
<data name="ReadOnlyPropertyAssignmentInspection" xml:space="preserve">
461461
<value>In general, the VBE editor catches this type of error and will not compile. However, there are a few scenarios where the error is overlooked by the compiler and an error is generated at runtime. To avoid a runtime error, implement the missing Property or Subroutine. </value>
462462
</data>
463+
<data name="SuspiciousPredeclaredInstanceAccessInspection" xml:space="preserve">
464+
<value>While a stateful default instance might be intentional, it is a common source of bugs and should be avoided. Use the 'Me' qualifier to explicitly refer to the current instance and eliminate any ambiguity.</value>
465+
</data>
463466
</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
@@ -460,4 +460,7 @@
460460
<data name="ReadOnlyPropertyAssignmentInspection" xml:space="preserve">
461461
<value>Read-Only Property assignment</value>
462462
</data>
463+
<data name="SuspiciousPredeclaredInstanceAccessInspection" xml:space="preserve">
464+
<value>Suspicious access to a predeclared instance</value>
465+
</data>
463466
</root>

Rubberduck.Resources/Inspections/InspectionResults.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/InspectionResults.resx

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -540,4 +540,8 @@ In memoriam, 1972-2018</value>
540540
<value>Attempt to assign Read-Only Property '{0}'</value>
541541
<comment>{0} Property name</comment>
542542
</data>
543+
<data name="SuspiciousPredeclaredInstanceAccessInspection" xml:space="preserve">
544+
<value>Identifier '{0}' in '{1}' is suspiciously referring to the default instance of that class type.</value>
545+
<comment>{0} identifier name; {1} expression/context</comment>
546+
</data>
543547
</root>

Rubberduck.Resources/Inspections/QuickFixes.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/QuickFixes.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -309,4 +309,7 @@
309309
<data name="AnnotateEntryPointQuickFix" xml:space="preserve">
310310
<value>Add @EntryPoint annotation</value>
311311
</data>
312+
<data name="ReplaceQualifierWithMeQuickFix" xml:space="preserve">
313+
<value>Replace qualifier with 'Me'</value>
314+
</data>
312315
</root>

0 commit comments

Comments
 (0)