@@ -144,38 +144,38 @@ public UnreachableCaseInspection(IDeclarationFinderProvider declarationFinderPro
144
144
protected override IEnumerable < IInspectionResult > DoGetInspectionResults ( )
145
145
{
146
146
var finder = DeclarationFinderProvider . DeclarationFinder ;
147
- var enumStmts = _listener . EnumerationStmtContexts ( ) ;
148
- var parseTreeValueVisitor = CreateParseTreeValueVisitor ( enumStmts , GetIdentifierReferenceForContext ) ;
149
147
150
148
return finder . UserDeclarations ( DeclarationType . Module )
151
149
. Where ( module => module != null )
152
- . SelectMany ( module => DoGetInspectionResults ( module . QualifiedModuleName , finder , parseTreeValueVisitor ) )
150
+ . SelectMany ( module => DoGetInspectionResults ( module . QualifiedModuleName , finder ) )
153
151
. ToList ( ) ;
154
152
}
155
153
156
154
protected override IEnumerable < IInspectionResult > DoGetInspectionResults ( QualifiedModuleName module )
157
155
{
158
156
var finder = DeclarationFinderProvider . DeclarationFinder ;
159
- var enumStmts = _listener . EnumerationStmtContexts ( ) ;
160
- var parseTreeValueVisitor = CreateParseTreeValueVisitor ( enumStmts , GetIdentifierReferenceForContext ) ;
161
- return DoGetInspectionResults ( module , finder , parseTreeValueVisitor ) ;
157
+ return DoGetInspectionResults ( module , finder ) ;
162
158
}
163
159
164
- private IEnumerable < IInspectionResult > DoGetInspectionResults ( QualifiedModuleName module , DeclarationFinder finder , IParseTreeValueVisitor parseTreeValueVisitor )
160
+ private IEnumerable < IInspectionResult > DoGetInspectionResults ( QualifiedModuleName module , DeclarationFinder finder )
165
161
{
166
162
var qualifiedSelectCaseStmts = Listener . Contexts ( module )
167
163
// ignore filtering here to make the search space smaller
168
164
. Where ( result => ! result . IsIgnoringInspectionResultFor ( finder , AnnotationName ) ) ;
169
165
166
+ var enumStmts = _listener . EnumerationStmtContexts ( ) ;
167
+ var parseTreeValueVisitor = CreateParseTreeValueVisitor ( enumStmts , context => GetIdentifierReferenceForContextFunction ( finder ) ( module , context ) ) ;
168
+
170
169
return qualifiedSelectCaseStmts
171
170
. SelectMany ( context => ResultsForContext ( context , finder , parseTreeValueVisitor ) )
172
171
. ToList ( ) ;
173
172
}
174
173
175
174
private IEnumerable < IInspectionResult > ResultsForContext ( QualifiedContext < ParserRuleContext > qualifiedSelectCaseStmt , DeclarationFinder finder , IParseTreeValueVisitor parseTreeValueVisitor )
176
175
{
177
- var contextValues = qualifiedSelectCaseStmt . Context . Accept ( parseTreeValueVisitor ) ;
178
- var selectCaseInspector = _unreachableCaseInspectorFactory . Create ( ( VBAParser . SelectCaseStmtContext ) qualifiedSelectCaseStmt . Context , contextValues , GetVariableTypeName ) ;
176
+ var module = qualifiedSelectCaseStmt . ModuleName ;
177
+ var contextValues = parseTreeValueVisitor . VisitChildren ( qualifiedSelectCaseStmt . Context ) ;
178
+ var selectCaseInspector = _unreachableCaseInspectorFactory . Create ( ( VBAParser . SelectCaseStmtContext ) qualifiedSelectCaseStmt . Context , contextValues , GetVariableTypeNameFunction ( module , finder ) ) ;
179
179
180
180
var results = selectCaseInspector . InspectForUnreachableCases ( ) ;
181
181
@@ -216,28 +216,33 @@ private IInspectionResult CreateInspectionResult(QualifiedContext<ParserRuleCont
216
216
new QualifiedContext < ParserRuleContext > ( selectStmt . ModuleName , unreachableBlock ) ) ;
217
217
}
218
218
219
- public IParseTreeValueVisitor CreateParseTreeValueVisitor ( IReadOnlyList < VBAParser . EnumerationStmtContext > allEnums , Func < ParserRuleContext , ( bool success , IdentifierReference idRef ) > func )
220
- => _parseTreeValueVisitorFactory . Create ( allEnums , func ) ;
219
+ public IParseTreeValueVisitor CreateParseTreeValueVisitor (
220
+ IReadOnlyList < QualifiedContext < VBAParser . EnumerationStmtContext > > allEnums ,
221
+ Func < ParserRuleContext , ( bool success , IdentifierReference idRef ) > func )
222
+ {
223
+ var enums = allEnums . Select ( item => item . Context ) . ToList ( ) ;
224
+ return _parseTreeValueVisitorFactory . Create ( enums , func ) ;
225
+ }
221
226
222
- //Method is used as a delegate to avoid propagating RubberduckParserState beyond this class
223
- private ( bool success , IdentifierReference idRef ) GetIdentifierReferenceForContext ( ParserRuleContext context )
227
+ private Func < QualifiedModuleName , ParserRuleContext , ( bool success , IdentifierReference idRef ) > GetIdentifierReferenceForContextFunction ( DeclarationFinder finder )
224
228
{
225
- return GetIdentifierReferenceForContext ( context , DeclarationFinderProvider ) ;
229
+ return ( module , context ) => GetIdentifierReferenceForContext ( module , context , finder ) ;
226
230
}
227
231
228
232
//public static to support tests
229
233
//FIXME There should not be additional public methods just for tests. This class seems to want to be split or at least reorganized.
230
- public static ( bool success , IdentifierReference idRef ) GetIdentifierReferenceForContext ( ParserRuleContext context , IDeclarationFinderProvider declarationFinderProvider )
234
+ public static ( bool success , IdentifierReference idRef ) GetIdentifierReferenceForContext ( QualifiedModuleName module , ParserRuleContext context , DeclarationFinder finder )
231
235
{
232
236
if ( context == null )
233
237
{
234
238
return ( false , null ) ;
235
239
}
236
240
237
- //FIXME Get the declaration finder only once inside the inspection to avoid the possibility of inconsistent state due to a reparse while inspections run.
238
- var finder = declarationFinderProvider . DeclarationFinder ;
239
- var identifierReferences = finder . MatchName ( context . GetText ( ) )
240
- . SelectMany ( declaration => declaration . References )
241
+ var qualifiedSelection = new QualifiedSelection ( module , context . GetSelection ( ) ) ;
242
+
243
+ var identifierReferences =
244
+ finder
245
+ . IdentifierReferences ( qualifiedSelection )
241
246
. Where ( reference => reference . Context == context )
242
247
. ToList ( ) ;
243
248
@@ -246,19 +251,31 @@ public static (bool success, IdentifierReference idRef) GetIdentifierReferenceFo
246
251
: ( false , null ) ;
247
252
}
248
253
249
- //Method is used as a delegate to avoid propogating RubberduckParserState beyond this class
250
- private string GetVariableTypeName ( string variableName , ParserRuleContext ancestor )
254
+ private Func < string , ParserRuleContext , string > GetVariableTypeNameFunction ( QualifiedModuleName module , DeclarationFinder finder )
251
255
{
252
- var descendents = ancestor . GetDescendents < VBAParser . SimpleNameExprContext > ( ) . Where ( desc => desc . GetText ( ) . Equals ( variableName ) ) . ToList ( ) ;
253
- if ( descendents . Any ( ) )
256
+ return ( variableName , ancestor ) => GetVariableTypeName ( module , variableName , ancestor , finder ) ;
257
+ }
258
+
259
+ private string GetVariableTypeName ( QualifiedModuleName module , string variableName , ParserRuleContext ancestor , DeclarationFinder finder )
260
+ {
261
+ if ( ancestor == null )
254
262
{
255
- ( bool success , IdentifierReference idRef ) = GetIdentifierReferenceForContext ( descendents . First ( ) , DeclarationFinderProvider ) ;
256
- if ( success )
257
- {
258
- return GetBaseTypeForDeclaration ( idRef . Declaration ) ;
259
- }
263
+ return string . Empty ;
264
+ }
265
+
266
+ var descendents = ancestor . GetDescendents < VBAParser . SimpleNameExprContext > ( )
267
+ . Where ( desc => desc . GetText ( ) . Equals ( variableName ) )
268
+ . ToList ( ) ;
269
+ if ( ! descendents . Any ( ) )
270
+ {
271
+ return string . Empty ;
260
272
}
261
- return string . Empty ;
273
+
274
+ var firstDescendent = descendents . First ( ) ;
275
+ var ( success , reference ) = GetIdentifierReferenceForContext ( module , firstDescendent , finder ) ;
276
+ return success ?
277
+ GetBaseTypeForDeclaration ( reference . Declaration )
278
+ : string . Empty ;
262
279
}
263
280
264
281
private string GetBaseTypeForDeclaration ( Declaration declaration )
@@ -277,8 +294,8 @@ private string GetBaseTypeForDeclaration(Declaration declaration)
277
294
#region UnreachableCaseInspectionListeners
278
295
public class UnreachableCaseInspectionListener : InspectionListenerBase
279
296
{
280
- private readonly IDictionary < QualifiedModuleName , List < VBAParser . EnumerationStmtContext > > _enumStmts = new Dictionary < QualifiedModuleName , List < VBAParser . EnumerationStmtContext > > ( ) ;
281
- public IReadOnlyList < VBAParser . EnumerationStmtContext > EnumerationStmtContexts ( ) => _enumStmts . AllValues ( ) . ToList ( ) ;
297
+ private readonly IDictionary < QualifiedModuleName , List < QualifiedContext < VBAParser . EnumerationStmtContext > > > _enumStmts = new Dictionary < QualifiedModuleName , List < QualifiedContext < VBAParser . EnumerationStmtContext > > > ( ) ;
298
+ public IReadOnlyList < QualifiedContext < VBAParser . EnumerationStmtContext > > EnumerationStmtContexts ( ) => _enumStmts . AllValues ( ) . ToList ( ) ;
282
299
283
300
public override void ClearContexts ( )
284
301
{
@@ -305,13 +322,14 @@ public override void EnterEnumerationStmt([NotNull] VBAParser.EnumerationStmtCon
305
322
private void SaveEnumStmt ( VBAParser . EnumerationStmtContext context )
306
323
{
307
324
var module = CurrentModuleName ;
325
+ var qualifiedContext = new QualifiedContext < VBAParser . EnumerationStmtContext > ( module , context ) ;
308
326
if ( _enumStmts . TryGetValue ( module , out var stmts ) )
309
327
{
310
- stmts . Add ( context ) ;
328
+ stmts . Add ( qualifiedContext ) ;
311
329
}
312
330
else
313
331
{
314
- _enumStmts . Add ( module , new List < VBAParser . EnumerationStmtContext > { context } ) ;
332
+ _enumStmts . Add ( module , new List < QualifiedContext < VBAParser . EnumerationStmtContext > > { qualifiedContext } ) ;
315
333
}
316
334
}
317
335
}
0 commit comments