Skip to content

Commit 60c347b

Browse files
authored
Merge pull request #5875 from BZngr/5803_MissingSetter
2 parents 8d90008 + 966b43a commit 60c347b

File tree

8 files changed

+354
-0
lines changed

8 files changed

+354
-0
lines changed
Lines changed: 134 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,134 @@
1+
using Rubberduck.CodeAnalysis.Inspections.Abstract;
2+
using Rubberduck.Parsing;
3+
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.Parsing.VBA.DeclarationCaching;
6+
using Rubberduck.Resources.Inspections;
7+
using System.Linq;
8+
9+
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
10+
{
11+
/// <summary>
12+
/// Identifies Property assigment references where Set or Let Property Members do not exist.
13+
/// </summary>
14+
/// <why>
15+
/// In general, the VBE editor catches this type of error and will not compile. However, there are
16+
/// a few scenarios where the error is overlooked by the compiler and an error is generated at runtime.
17+
/// To avoid the runtime error scenarios, the inspection flags all assignment references of a read-only property.
18+
/// </why>
19+
/// <example hasResult="true">
20+
/// <module name="MyDataObject" type="Class Module">
21+
/// <![CDATA[
22+
/// Public myData As Long
23+
/// ]]>
24+
/// </module>
25+
/// <module name="Client" type="Standard Module">
26+
/// <![CDATA[
27+
/// Private myDataObj As MyDataObject
28+
///
29+
/// Public Sub Test()
30+
/// Set TheData = new MyDataObject
31+
/// End Sub
32+
///
33+
/// Public Property Get TheData() As MyDataObject
34+
/// Set TheData = myDataObj
35+
/// End Property
36+
/// ]]>
37+
/// </module>
38+
/// </example>
39+
/// <example hasResult="false">
40+
/// <module name="MyDataObject" type="Class Module">
41+
/// <![CDATA[
42+
/// Public myData As Long
43+
/// ]]>
44+
/// </module>
45+
/// <module name="MyModule" type="Standard Module">
46+
/// <![CDATA[
47+
/// Private myDataObj As MyDataObject
48+
///
49+
/// Public Sub Test()
50+
/// Set TheData = new MyDataObject
51+
/// End Sub
52+
///
53+
/// Public Property Get TheData() As MyDataObject
54+
/// Set TheData = myDataObj
55+
/// End Property
56+
/// Public Property Set TheData(RHS As MyDataObject)
57+
/// Set myDataObj = RHS
58+
/// End Property
59+
/// ]]>
60+
/// </module>
61+
/// </example>
62+
/// <example hasResult="true">
63+
/// <module name="MyModule" type="Standard Module">
64+
/// <![CDATA[
65+
/// Private myData As Variant
66+
///
67+
/// Public Sub Test()
68+
/// TheData = 45
69+
/// End Sub
70+
///
71+
/// Public Property Get TheData() As Variant
72+
/// TheData = myData
73+
/// End Property
74+
/// ]]>
75+
/// </module>
76+
/// </example>
77+
/// <example hasResult="false">
78+
/// <module name="Client" type="Standard Module">
79+
/// <![CDATA[
80+
/// Private myData As Variant
81+
///
82+
/// Public Sub Test()
83+
/// TheData = 45
84+
/// End Sub
85+
///
86+
/// Public Property Get TheData() As Variant
87+
/// TheData = myData
88+
/// End Property
89+
/// Public Property Let TheData(RHS As Variant)
90+
/// myData = RHS
91+
/// End Property
92+
/// ]]>
93+
/// </module>
94+
/// </example>
95+
internal sealed class ReadOnlyPropertyAssignmentInspection : IdentifierReferenceInspectionBase
96+
{
97+
public ReadOnlyPropertyAssignmentInspection(IDeclarationFinderProvider declarationFinderProvider)
98+
: base(declarationFinderProvider)
99+
{ }
100+
101+
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
102+
{
103+
if (!reference.Declaration.DeclarationType.HasFlag(DeclarationType.Property)
104+
//Ignore expressions found within Property declaration contexts
105+
|| reference.Declaration.Context.Contains(reference.Context))
106+
{
107+
return false;
108+
}
109+
110+
var propertyDeclarations = finder.MatchName(reference.Declaration.IdentifierName)
111+
.Where(d => d.DeclarationType.HasFlag(DeclarationType.Property)
112+
&& d.QualifiedModuleName == reference.QualifiedModuleName);
113+
114+
if (reference.IsSetAssignment)
115+
{
116+
return !propertyDeclarations.Any(pd => pd.DeclarationType.HasFlag(DeclarationType.PropertySet));
117+
}
118+
119+
if (reference.IsAssignment && !reference.IsSetAssignment)
120+
{
121+
return !propertyDeclarations.Any(pd => pd.DeclarationType.HasFlag(DeclarationType.PropertyLet));
122+
}
123+
124+
return false;
125+
}
126+
127+
protected override string ResultDescription(IdentifierReference reference)
128+
{
129+
var identifierName = reference.IdentifierName;
130+
return string.Format(
131+
InspectionResults.ReadOnlyPropertyAssignmentInspection, identifierName);
132+
}
133+
}
134+
}

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
@@ -457,6 +457,9 @@ If the parameter can be null, ignore this inspection result; passing a null valu
457457
<data name="UnrecognizedAnnotationInspection" xml:space="preserve">
458458
<value>A comment was parsed as a syntactically valid annotation, but not recognized as a supported annotation type.</value>
459459
</data>
460+
<data name="ReadOnlyPropertyAssignmentInspection" xml:space="preserve">
461+
<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>
462+
</data>
460463
<data name="SuspiciousPredeclaredInstanceAccessInspection" xml:space="preserve">
461464
<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>
462465
</data>

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
@@ -457,6 +457,9 @@
457457
<data name="UnrecognizedAnnotationInspection" xml:space="preserve">
458458
<value>Unrecognized annotation</value>
459459
</data>
460+
<data name="ReadOnlyPropertyAssignmentInspection" xml:space="preserve">
461+
<value>Read-Only Property assignment</value>
462+
</data>
460463
<data name="SuspiciousPredeclaredInstanceAccessInspection" xml:space="preserve">
461464
<value>Suspicious access to a predeclared instance</value>
462465
</data>

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
@@ -536,6 +536,10 @@ In memoriam, 1972-2018</value>
536536
<value>'{0}' is not a recognized Rubberduck annotation (yet?)</value>
537537
<comment>{0} Unrecognized annotation name</comment>
538538
</data>
539+
<data name="ReadOnlyPropertyAssignmentInspection" xml:space="preserve">
540+
<value>Attempt to assign Read-Only Property '{0}'</value>
541+
<comment>{0} Property name</comment>
542+
</data>
539543
<data name="SuspiciousPredeclaredInstanceAccessInspection" xml:space="preserve">
540544
<value>Identifier '{0}' in '{1}' is suspiciously referring to the default instance of that class type.</value>
541545
<comment>{0} identifier name; {1} expression/context</comment>
Lines changed: 183 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,183 @@
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 ReadOnlyPropertyAssignmentTests : InspectionTestsBase
17+
{
18+
[Test]
19+
[Category("Inspections")]
20+
[Category("ReadOnlyPropertyAssignment")]
21+
public void SetUserDefinedClassMCVE_Flags()
22+
{
23+
var sutInputCode =
24+
@"Private mData As AClass
25+
26+
Public Sub Test()
27+
Set MyData = New AClass
28+
End Sub
29+
30+
Public Property Get MyData() As AClass
31+
Set MyData = mData
32+
End Property
33+
";
34+
Assert.AreEqual(1, InspectionResultsForModules(
35+
(MockVbeBuilder.TestModuleName, sutInputCode, ComponentType.StandardModule),
36+
("AClass", $"Option Explicit{Environment.NewLine}", ComponentType.ClassModule)).Count());
37+
}
38+
39+
[Test]
40+
[Category("Inspections")]
41+
[Category("ReadOnlyPropertyAssignment")]
42+
public void SetUserDefinedClassSetExists_NotFlagged()
43+
{
44+
var sutInputCode =
45+
@"Private mData As AClass
46+
47+
Public Sub Test()
48+
Set MyData = New AClass
49+
End Sub
50+
51+
Public Property Get MyData() As AClass
52+
Set MyData = mData
53+
End Property
54+
Public Property Set MyData(RHS As AClass)
55+
Set mData = MyData
56+
End Property
57+
";
58+
Assert.AreEqual(0, InspectionResultsForModules(
59+
(MockVbeBuilder.TestModuleName, sutInputCode, ComponentType.StandardModule),
60+
("AClass", $"Option Explicit{Environment.NewLine}", ComponentType.ClassModule)).Count());
61+
}
62+
63+
[Test]
64+
[Category("Inspections")]
65+
[Category("ReadOnlyPropertyAssignment")]
66+
public void LetVariantMCVE_Flags()
67+
{
68+
var sutInputCode =
69+
@"Option Explicit
70+
71+
Private myVariant As Variant
72+
73+
Public Sub Test()
74+
TheVariant = 7
75+
End Sub
76+
77+
Public Property Get TheVariant() As Variant
78+
If IsObject(myVariant) Then
79+
Set TheVariant = myVariant
80+
Else
81+
TheVariant = myVariant
82+
End If
83+
End Property
84+
";
85+
86+
Assert.AreEqual(1, InspectionResultsForModules(
87+
(MockVbeBuilder.TestModuleName, sutInputCode, ComponentType.StandardModule)).Count());
88+
}
89+
90+
[Test]
91+
[Category("Inspections")]
92+
[Category("ReadOnlyPropertyAssignment")]
93+
public void LetVariantLetExists_NotFlagged()
94+
{
95+
var sutInputCode =
96+
@"Option Explicit
97+
98+
Private myVariant As Variant
99+
100+
Public Sub Test()
101+
TheVariant = 7
102+
End Sub
103+
104+
Public Property Get TheVariant() As Variant
105+
If IsObject(myVariant) Then
106+
Set TheVariant = myVariant
107+
Else
108+
TheVariant = myVariant
109+
End If
110+
End Property
111+
Public Property Let TheVariant(RHS As Variant)
112+
myVariant = RHS
113+
End Property
114+
";
115+
Assert.AreEqual(0, InspectionResultsForModules(
116+
(MockVbeBuilder.TestModuleName, sutInputCode, ComponentType.StandardModule)).Count());
117+
}
118+
119+
[Test]
120+
[Category("Inspections")]
121+
[Category("ReadOnlyPropertyAssignment")]
122+
public void SetVariantMCVE_Flags()
123+
{
124+
var sutInputCode =
125+
@"Option Explicit
126+
127+
Private myVariant As Variant
128+
129+
Public Sub Test()
130+
Set TheVariant = new AClass
131+
End Sub
132+
133+
Public Property Get TheVariant() As Variant
134+
If IsObject(myVariant) Then
135+
Set TheVariant = myVariant
136+
Else
137+
TheVariant = myVariant
138+
End If
139+
End Property
140+
";
141+
142+
Assert.AreEqual(1, InspectionResultsForModules(
143+
(MockVbeBuilder.TestModuleName, sutInputCode, ComponentType.StandardModule),
144+
("AClass", $"Option Explicit{Environment.NewLine}", ComponentType.ClassModule)).Count());
145+
}
146+
147+
[Test]
148+
[Category("Inspections")]
149+
[Category("ReadOnlyPropertyAssignment")]
150+
public void SetVariantSetExists_NotFlagged()
151+
{
152+
var sutInputCode =
153+
@"Option Explicit
154+
155+
Private myVariant As Variant
156+
157+
Public Sub Test()
158+
Set TheVariant = new AClass
159+
End Sub
160+
161+
Public Property Get TheVariant() As Variant
162+
If IsObject(myVariant) Then
163+
Set TheVariant = myVariant
164+
Else
165+
TheVariant = myVariant
166+
End If
167+
End Property
168+
Public Property Set TheVariant(RHS As Variant)
169+
Set myVariant = RHS
170+
End Property
171+
";
172+
173+
Assert.AreEqual(0, InspectionResultsForModules(
174+
(MockVbeBuilder.TestModuleName, sutInputCode, ComponentType.StandardModule),
175+
("AClass", $"Option Explicit{Environment.NewLine}", ComponentType.ClassModule)).Count());
176+
}
177+
178+
protected override IInspection InspectionUnderTest(RubberduckParserState state)
179+
{
180+
return new ReadOnlyPropertyAssignmentInspection(state);
181+
}
182+
}
183+
}

0 commit comments

Comments
 (0)