@@ -15,13 +15,14 @@ namespace RubberduckTests.Inspections
15
15
[ TestFixture ]
16
16
public class ReadOnlyPropertyAssignmentTests : InspectionTestsBase
17
17
{
18
- [ Test ]
18
+ [ TestCase ( "MyData" , 0 ) ]
19
+ [ TestCase ( "MyData2" , 1 ) ] //Results in a readonly MyData property
19
20
[ Category ( "Inspections" ) ]
20
21
[ Category ( "ReadOnlyPropertyAssignment" ) ]
21
- public void SetUserDefinedClassMCVE_Flags ( )
22
+ public void SetUserDefinedClass_CalledFromSameModule ( string setPropertyName , long expectedCount )
22
23
{
23
24
var sutInputCode =
24
- @"Private mData As AClass
25
+ $ @ "Private mData As AClass
25
26
26
27
Public Sub Test()
27
28
Set MyData = New AClass
@@ -30,48 +31,59 @@ End Sub
30
31
Public Property Get MyData() As AClass
31
32
Set MyData = mData
32
33
End Property
34
+
35
+ Public Property Set { setPropertyName } (RHS As AClass)
36
+ Set mData = MyData
37
+ End Property
33
38
" ;
34
- Assert . AreEqual ( 1 , InspectionResultsForModules (
39
+ Assert . AreEqual ( expectedCount , InspectionResultsForModules (
35
40
( MockVbeBuilder . TestModuleName , sutInputCode , ComponentType . StandardModule ) ,
36
41
( "AClass" , $ "Option Explicit{ Environment . NewLine } ", ComponentType . ClassModule ) ) . Count ( ) ) ;
37
42
}
38
43
39
- [ Test ]
44
+ [ TestCase ( "TheVariant" , 0 ) ]
45
+ [ TestCase ( "TheVariant2" , 1 ) ] //Results in a readonly MyData property
40
46
[ Category ( "Inspections" ) ]
41
47
[ Category ( "ReadOnlyPropertyAssignment" ) ]
42
- public void SetUserDefinedClassSetExists_NotFlagged ( )
48
+ public void VariantLet_CalledFromSameModule ( string letPropertyName , long expectedCount )
43
49
{
44
50
var sutInputCode =
45
- @"Private mData As AClass
51
+ $@ "Option Explicit
52
+
53
+ Private myVariant As Variant
46
54
47
55
Public Sub Test()
48
- Set MyData = New AClass
56
+ TheVariant = 7
49
57
End Sub
50
58
51
- Public Property Get MyData() As AClass
52
- Set MyData = mData
59
+ Public Property Get TheVariant() As Variant
60
+ If IsObject(myVariant) Then
61
+ Set TheVariant = myVariant
62
+ Else
63
+ TheVariant = myVariant
64
+ End If
53
65
End Property
54
- Public Property Set MyData (RHS As AClass )
55
- Set mData = MyData
66
+ Public Property Let { letPropertyName } (RHS As Variant )
67
+ myVariant = RHS
56
68
End Property
57
69
" ;
58
- Assert . AreEqual ( 0 , InspectionResultsForModules (
59
- ( MockVbeBuilder . TestModuleName , sutInputCode , ComponentType . StandardModule ) ,
60
- ( "AClass" , $ "Option Explicit{ Environment . NewLine } ", ComponentType . ClassModule ) ) . Count ( ) ) ;
70
+ Assert . AreEqual ( expectedCount , InspectionResultsForModules (
71
+ ( MockVbeBuilder . TestModuleName , sutInputCode , ComponentType . StandardModule ) ) . Count ( ) ) ;
61
72
}
62
73
63
- [ Test ]
74
+ [ TestCase ( "TheVariant" , 0 ) ]
75
+ [ TestCase ( "TheVariant2" , 1 ) ] //Results in a readonly MyData property
64
76
[ Category ( "Inspections" ) ]
65
77
[ Category ( "ReadOnlyPropertyAssignment" ) ]
66
- public void LetVariantMCVE_Flags ( )
78
+ public void VariantSet_CalledFromSameModule ( string setPropertyName , long expectedCount )
67
79
{
68
80
var sutInputCode =
69
- @"Option Explicit
81
+ $ @ "Option Explicit
70
82
71
83
Private myVariant As Variant
72
84
73
85
Public Sub Test()
74
- TheVariant = 7
86
+ Set TheVariant = new AClass
75
87
End Sub
76
88
77
89
Public Property Get TheVariant() As Variant
@@ -81,98 +93,140 @@ If IsObject(myVariant) Then
81
93
TheVariant = myVariant
82
94
End If
83
95
End Property
96
+ Public Property Set { setPropertyName } (RHS As Variant)
97
+ Set myVariant = RHS
98
+ End Property
84
99
" ;
85
100
86
- Assert . AreEqual ( 1 , InspectionResultsForModules (
87
- ( MockVbeBuilder . TestModuleName , sutInputCode , ComponentType . StandardModule ) ) . Count ( ) ) ;
101
+ Assert . AreEqual ( expectedCount , InspectionResultsForModules (
102
+ ( MockVbeBuilder . TestModuleName , sutInputCode , ComponentType . StandardModule ) ,
103
+ ( "AClass" , $ "Option Explicit{ Environment . NewLine } ", ComponentType . ClassModule ) ) . Count ( ) ) ;
88
104
}
89
105
90
- [ Test ]
106
+ [ TestCase ( "MyData" , 0 ) ]
107
+ [ TestCase ( "MyData2" , 1 ) ] //Results in a readonly MyData property
91
108
[ Category ( "Inspections" ) ]
92
109
[ Category ( "ReadOnlyPropertyAssignment" ) ]
93
- public void LetVariantLetExists_NotFlagged ( )
110
+ public void ObjectDataType_CalledFromOtherModule ( string setPropertyName , long expectedCount )
94
111
{
95
112
var sutInputCode =
96
- @"Option Explicit
113
+ $@ "
114
+ Option Explicit
97
115
98
- Private myVariant As Variant
116
+ Private mData As Collection
99
117
100
118
Public Sub Test()
101
- TheVariant = 7
119
+ Set MyData = New Collection
102
120
End Sub
103
121
104
- Public Property Get TheVariant() As Variant
105
- If IsObject(myVariant) Then
106
- Set TheVariant = myVariant
107
- Else
108
- TheVariant = myVariant
109
- End If
122
+ Public Property Get MyData() As Collection
123
+ Set MyData = mData
110
124
End Property
111
- Public Property Let TheVariant(RHS As Variant)
112
- myVariant = RHS
125
+
126
+ Public Property Set { setPropertyName } (ByVal RHS As Collection)
127
+ Set mData = RHS
113
128
End Property
114
129
" ;
115
- Assert . AreEqual ( 0 , InspectionResultsForModules (
116
- ( MockVbeBuilder . TestModuleName , sutInputCode , ComponentType . StandardModule ) ) . Count ( ) ) ;
130
+
131
+ var callingModule =
132
+ $@ "
133
+ Option Explicit
134
+
135
+ Public Sub Test()
136
+ Set { MockVbeBuilder . TestModuleName } .MyData = New Collection
137
+ End Sub
138
+ " ;
139
+
140
+ Assert . AreEqual ( expectedCount , InspectionResultsForModules (
141
+ ( MockVbeBuilder . TestModuleName , sutInputCode , ComponentType . StandardModule ) ,
142
+ ( "CallingModule" , callingModule , ComponentType . StandardModule ) ) . Count ( ) ) ;
117
143
}
118
144
119
- [ Test ]
145
+ [ TestCase ( "MyData" , 0 ) ]
146
+ [ TestCase ( "MyData2" , 1 ) ] //Results in a readonly MyData property
120
147
[ Category ( "Inspections" ) ]
121
148
[ Category ( "ReadOnlyPropertyAssignment" ) ]
122
- public void SetVariantMCVE_Flags ( )
149
+ public void ScalarDataType_CalledFromOtherModule ( string letPropertyName , long expectedCount )
123
150
{
124
151
var sutInputCode =
125
- @"Option Explicit
152
+ $@ "
153
+ Option Explicit
126
154
127
- Private myVariant As Variant
155
+ Private mData As Long
128
156
129
157
Public Sub Test()
130
- Set TheVariant = new AClass
158
+ Set MyData = 8
131
159
End Sub
132
160
133
- Public Property Get TheVariant() As Variant
134
- If IsObject(myVariant) Then
135
- Set TheVariant = myVariant
136
- Else
137
- TheVariant = myVariant
138
- End If
161
+ Public Property Get MyData() As Long
162
+ MyData = mData
139
163
End Property
164
+
165
+ Public Property Let { letPropertyName } (ByVal RHS As Long)
166
+ mData = RHS
167
+ End Property
168
+ " ;
169
+
170
+ var callingModule =
171
+ $@ "
172
+ Option Explicit
173
+
174
+ Public Sub Test()
175
+ { MockVbeBuilder . TestModuleName } .MyData = 80
176
+ End Sub
140
177
" ;
141
178
142
- Assert . AreEqual ( 1 , InspectionResultsForModules (
179
+ Assert . AreEqual ( expectedCount , InspectionResultsForModules (
143
180
( MockVbeBuilder . TestModuleName , sutInputCode , ComponentType . StandardModule ) ,
144
- ( "AClass " , $ "Option Explicit { Environment . NewLine } " , ComponentType . ClassModule ) ) . Count ( ) ) ;
181
+ ( "CallingModule " , callingModule , ComponentType . StandardModule ) ) . Count ( ) ) ;
145
182
}
146
183
184
+ //TODO: Remove 'Ignore' once this false positive scenario is resolved
147
185
[ Test ]
186
+ [ Ignore ( "False Positive" ) ]
148
187
[ Category ( "Inspections" ) ]
149
188
[ Category ( "ReadOnlyPropertyAssignment" ) ]
150
- public void SetVariantSetExists_NotFlagged ( )
189
+ public void FalsePositiveMCVE_ShouldNotFlag ( )
151
190
{
152
- var sutInputCode =
153
- @"Option Explicit
191
+ var fooClassCode =
192
+ @"
193
+ Option Explicit
154
194
155
- Private myVariant As Variant
195
+ Private mFooValue As String
156
196
157
- Public Sub Test()
158
- Set TheVariant = new AClass
197
+ 'If you remove this Sub, the false positive does not occur
198
+ Private Sub Class_Initialize()
199
+ mFooValue = ""Test""
159
200
End Sub
160
201
161
- Public Property Get TheVariant() As Variant
162
- If IsObject(myVariant) Then
163
- Set TheVariant = myVariant
164
- Else
165
- TheVariant = myVariant
166
- End If
202
+ Public Property Get FooValue() As String
203
+ FooValue = mFooValue
167
204
End Property
168
- Public Property Set TheVariant(RHS As Variant)
169
- Set myVariant = RHS
205
+
206
+ Public Property Let FooValue(ByVal RHS As String)
207
+ mFooValue = RHS
208
+ End Property
209
+ " ;
210
+ var sutInputCode =
211
+ @"
212
+ Option Explicit
213
+
214
+ 'If Sub Test is placed after Property Get FooValue the
215
+ 'False Positive does not occur
216
+ Public Sub Test()
217
+ Dim fc As FooClass
218
+ Set fc = New FooClass
219
+ fc.FooValue = FooValue
220
+ End Sub
221
+
222
+ Public Property Get FooValue() As String
223
+ FooValue = ""Test""
170
224
End Property
171
225
" ;
172
226
173
227
Assert . AreEqual ( 0 , InspectionResultsForModules (
174
228
( MockVbeBuilder . TestModuleName , sutInputCode , ComponentType . StandardModule ) ,
175
- ( "AClass " , $ "Option Explicit { Environment . NewLine } " , ComponentType . ClassModule ) ) . Count ( ) ) ;
229
+ ( "FooClass " , fooClassCode , ComponentType . ClassModule ) ) . Count ( ) ) ;
176
230
}
177
231
178
232
protected override IInspection InspectionUnderTest ( RubberduckParserState state )
0 commit comments