@@ -106,25 +106,28 @@ private static IEnumerable<IdentifierReference> FindUnusedAssignmentReferences(D
106
106
var tree = walker . GenerateTree ( localVariable . ParentScopeDeclaration . Context , localVariable ) ;
107
107
108
108
var allAssignmentsAndReferences = tree . Nodes ( new [ ] { typeof ( AssignmentNode ) , typeof ( ReferenceNode ) } )
109
- . Where ( node => localVariable . References . Contains ( node . Reference ) ) ;
109
+ . Where ( node => localVariable . References . Contains ( node . Reference ) )
110
+ . ToList ( ) ;
110
111
111
112
var unusedAssignmentNodes = allAssignmentsAndReferences . Any ( n => n is ReferenceNode )
112
113
? FindUnusedAssignmentNodes ( tree , localVariable , allAssignmentsAndReferences )
113
114
: allAssignmentsAndReferences . OfType < AssignmentNode > ( ) ;
114
115
115
- return unusedAssignmentNodes . Except ( FindDescendantsOfNeverFlagNodeTypes ( unusedAssignmentNodes ) )
116
+ return unusedAssignmentNodes . Where ( n => ! IsDescendentOfNeverFlagNode ( n ) )
116
117
. Select ( n => n . Reference ) ;
117
118
}
118
119
119
120
private static IEnumerable < AssignmentNode > FindUnusedAssignmentNodes ( INode node , Declaration localVariable , IEnumerable < INode > allAssignmentsAndReferences )
120
121
{
121
122
var assignmentExprNodes = node . Nodes ( new [ ] { typeof ( AssignmentExpressionNode ) } )
122
- . Where ( n => localVariable . References . Contains ( n . Children . FirstOrDefault ( ) ? . Reference ) ) ;
123
+ . Where ( n => localVariable . References . Contains ( n . Children . FirstOrDefault ( ) ? . Reference ) )
124
+ . ToList ( ) ;
123
125
124
126
var usedAssignments = new List < AssignmentNode > ( ) ;
125
127
foreach ( var refNode in allAssignmentsAndReferences . OfType < ReferenceNode > ( ) . Reverse ( ) )
126
128
{
127
- var assignmentExprNodesWithReference = assignmentExprNodes . Where ( n => n . Nodes ( new [ ] { typeof ( ReferenceNode ) } )
129
+ var assignmentExprNodesWithReference = assignmentExprNodes
130
+ . Where ( n => n . Nodes ( new [ ] { typeof ( ReferenceNode ) } )
128
131
. Contains ( refNode ) ) ;
129
132
130
133
var assignmentsPrecedingReference = assignmentExprNodesWithReference . Any ( )
@@ -144,30 +147,14 @@ private static IEnumerable<AssignmentNode> FindUnusedAssignmentNodes(INode node,
144
147
. Except ( usedAssignments ) ;
145
148
}
146
149
147
- private static IEnumerable < AssignmentNode > FindDescendantsOfNeverFlagNodeTypes ( IEnumerable < AssignmentNode > flaggedAssignments )
150
+ private static bool IsDescendentOfNeverFlagNode ( AssignmentNode assignment )
148
151
{
149
- var filteredResults = new List < AssignmentNode > ( ) ;
150
-
151
- foreach ( var assignment in flaggedAssignments )
152
- {
153
- if ( assignment . TryGetAncestorNode < BranchNode > ( out _ ) )
154
- {
155
- filteredResults . Add ( assignment ) ;
156
- }
157
- if ( assignment . TryGetAncestorNode < LoopNode > ( out _ ) )
158
- {
159
- filteredResults . Add ( assignment ) ;
160
- }
161
- }
162
- return filteredResults ;
152
+ return assignment . TryGetAncestorNode < BranchNode > ( out _ )
153
+ || assignment . TryGetAncestorNode < LoopNode > ( out _ ) ;
163
154
}
164
155
165
156
private static bool IsAssignmentOfNothing ( IdentifierReference reference )
166
157
{
167
- if ( reference . Context . Parent is VBAParser . SetStmtContext setStmtContext2 )
168
- {
169
- var test = setStmtContext2 . expression ( ) ;
170
- }
171
158
return reference . IsSetAssignment
172
159
&& reference . Context . Parent is VBAParser . SetStmtContext setStmtContext
173
160
&& setStmtContext . expression ( ) . GetText ( ) . Equals ( Tokens . Nothing ) ;
@@ -179,25 +166,25 @@ private static bool IsAssignmentOfNothing(IdentifierReference reference)
179
166
/// </summary>
180
167
/// <remarks>
181
168
/// Filters Assignment references that meet the following conditions:
182
- /// 1. Precedes a GoTo or Resume statement that branches execution to a line before the
183
- /// assignment reference, and
169
+ /// 1. Reference precedes a GoTo or Resume statement that branches execution to a line before the
170
+ /// assignment reference, AND
184
171
/// 2. A non-assignment reference is present on a line that is:
185
- /// a) At or below the start of the execution branch, and
172
+ /// a) At or below the start of the execution branch, AND
186
173
/// b) Above the next ExitStatement line (if one exists) or the end of the procedure
187
174
/// </remarks>
188
175
private static bool IsPotentiallyUsedViaJump ( IdentifierReference resultCandidate , DeclarationFinder finder )
189
176
{
190
177
if ( ! resultCandidate . Declaration . References . Any ( rf => ! rf . IsAssignment ) ) { return false ; }
191
178
192
- var labelIdLineNumberPairs = finder . DeclarationsWithType ( DeclarationType . LineLabel )
179
+ var labelIdLineNumberPairs = finder . Members ( resultCandidate . QualifiedModuleName , DeclarationType . LineLabel )
193
180
. Where ( label => resultCandidate . ParentScoping . Equals ( label . ParentDeclaration ) )
194
- . Select ( lbl => ( lbl . IdentifierName , lbl . Context . Start . Line ) ) ;
181
+ . ToDictionary ( key => key . IdentifierName , v => v . Context . Start . Line ) ;
195
182
196
183
return JumpStmtPotentiallyUsesVariable < VBAParser . GoToStmtContext > ( resultCandidate , labelIdLineNumberPairs )
197
184
|| JumpStmtPotentiallyUsesVariable < VBAParser . ResumeStmtContext > ( resultCandidate , labelIdLineNumberPairs ) ;
198
185
}
199
186
200
- private static bool JumpStmtPotentiallyUsesVariable < T > ( IdentifierReference resultCandidate , IEnumerable < ( string IdentifierName , int Line ) > labelIdLineNumberPairs ) where T : ParserRuleContext
187
+ private static bool JumpStmtPotentiallyUsesVariable < T > ( IdentifierReference resultCandidate , Dictionary < string , int > labelIdLineNumberPairs ) where T : ParserRuleContext
201
188
{
202
189
if ( TryGetRelevantJumpContext < T > ( resultCandidate , out var jumpStmt ) )
203
190
{
@@ -210,25 +197,27 @@ private static bool JumpStmtPotentiallyUsesVariable<T>(IdentifierReference resul
210
197
private static bool TryGetRelevantJumpContext < T > ( IdentifierReference resultCandidate , out T ctxt ) where T : ParserRuleContext
211
198
{
212
199
ctxt = resultCandidate . ParentScoping . Context . GetDescendents < T > ( )
213
- . Where ( sc => sc . Start . Line > resultCandidate . Context . Start . Line
214
- || ( sc . Start . Line == resultCandidate . Context . Start . Line
215
- && sc . Start . Column > resultCandidate . Context . Start . Column ) )
216
- . OrderBy ( sc => sc . Start . Line - resultCandidate . Context . Start . Line )
217
- . ThenBy ( sc => sc . Start . Column - resultCandidate . Context . Start . Column )
200
+ . Where ( descendent => descendent . GetSelection ( ) > resultCandidate . Selection )
201
+ . OrderBy ( descendent => descendent . GetSelection ( ) )
218
202
. FirstOrDefault ( ) ;
219
203
return ctxt != null ;
220
204
}
221
205
222
- private static bool IsPotentiallyUsedAssignment < T > ( T jumpContext , IdentifierReference resultCandidate , IEnumerable < ( string , int ) > labelIdLineNumberPairs )
206
+ private static bool IsPotentiallyUsedAssignment < T > ( T jumpContext , IdentifierReference resultCandidate , Dictionary < string , int > labelIdLineNumberPairs ) where T : ParserRuleContext
223
207
{
224
208
int ? executionBranchLine = null ;
225
- if ( jumpContext is VBAParser . GoToStmtContext gotoCtxt )
226
- {
227
- executionBranchLine = DetermineLabeledExecutionBranchLine ( gotoCtxt . expression ( ) . GetText ( ) , labelIdLineNumberPairs ) ;
228
- }
229
- else
209
+
210
+ switch ( jumpContext )
230
211
{
231
- executionBranchLine = DetermineResumeStmtExecutionBranchLine ( jumpContext as VBAParser . ResumeStmtContext , resultCandidate , labelIdLineNumberPairs ) ;
212
+ case VBAParser . GoToStmtContext gotoStmt :
213
+ executionBranchLine = labelIdLineNumberPairs [ gotoStmt . expression ( ) . GetText ( ) ] ;
214
+ break ;
215
+ case VBAParser . ResumeStmtContext resume :
216
+ executionBranchLine = DetermineResumeStmtExecutionBranchLine ( resume , resultCandidate , labelIdLineNumberPairs ) ;
217
+ break ;
218
+ default :
219
+ executionBranchLine = null ;
220
+ break ;
232
221
}
233
222
234
223
return executionBranchLine . HasValue
@@ -256,49 +245,57 @@ private static bool AssignmentIsUsedPriorToExitStmts(IdentifierReference resultC
256
245
return ! ( sortedContextsAfterBranch . FirstOrDefault ( ) is VBAParser . ExitStmtContext ) ;
257
246
}
258
247
259
- private static int ? DetermineResumeStmtExecutionBranchLine ( VBAParser . ResumeStmtContext resumeStmt , IdentifierReference resultCandidate , IEnumerable < ( string IdentifierName , int Line ) > labelIdLineNumberPairs )
248
+ private static int ? DetermineResumeStmtExecutionBranchLine ( VBAParser . ResumeStmtContext resumeStmt , IdentifierReference resultCandidate , Dictionary < string , int > labelIdLineNumberPairs )
260
249
{
261
250
var onErrorGotoLabelToLineNumber = resultCandidate . ParentScoping . Context . GetDescendents < VBAParser . OnErrorStmtContext > ( )
262
- . Where ( errorStmtCtxt => ! errorStmtCtxt . expression ( ) . GetText ( ) . Equals ( "0" ) )
251
+ . Where ( errorStmtCtxt => IsBranchingOnErrorGoToLabel ( errorStmtCtxt ) )
263
252
. ToDictionary ( k => k . expression ( ) ? . GetText ( ) ?? "No Label" , v => v . Start . Line ) ;
264
253
265
254
var errorHandlerLabelsAndLines = labelIdLineNumberPairs
266
- . Where ( pair => onErrorGotoLabelToLineNumber . ContainsKey ( pair . IdentifierName ) ) ;
255
+ . Where ( pair => onErrorGotoLabelToLineNumber . ContainsKey ( pair . Key ) ) ;
267
256
268
257
//Labels must be located at the start of a line.
269
258
//If the resultCandidate line precedes all error handling related labels,
270
259
//a Resume statement cannot be invoked (successfully) for the resultCandidate
271
- if ( ! errorHandlerLabelsAndLines . Any ( s => s . Line <= resultCandidate . Context . Start . Line ) )
260
+ if ( ! errorHandlerLabelsAndLines . Any ( kvp => kvp . Value <= resultCandidate . Context . Start . Line ) )
272
261
{
273
262
return null ;
274
263
}
275
264
276
- var expression = resumeStmt . expression ( ) ? . GetText ( ) ;
265
+ var resumeStmtExpression = resumeStmt . expression ( ) ? . GetText ( ) ;
277
266
278
267
//For Resume and Resume Next, expression() is null
279
- if ( string . IsNullOrEmpty ( expression ) )
268
+ if ( string . IsNullOrEmpty ( resumeStmtExpression ) )
280
269
{
281
- //Get errorHandlerLabel for the Resume statement
282
- string errorHandlerLabel = errorHandlerLabelsAndLines
283
- . Where ( pair => resumeStmt . Start . Line >= pair . Line )
284
- . OrderBy ( pair => resumeStmt . Start . Line - pair . Line )
285
- . Select ( pair => pair . IdentifierName )
270
+ var errorHandlerLabelForTheResumeStatement = errorHandlerLabelsAndLines
271
+ . Where ( kvp => resumeStmt . Start . Line >= kvp . Value )
272
+ . OrderBy ( kvp => resumeStmt . Start . Line - kvp . Value )
273
+ . Select ( kvp => kvp . Key )
286
274
. FirstOrDefault ( ) ;
287
275
288
276
//Since the execution branch line for Resume and Resume Next statements
289
277
//is indeterminant by static analysis, the On***GoTo statement
290
278
//is used as the execution branch line
291
- return onErrorGotoLabelToLineNumber [ errorHandlerLabel ] ;
279
+ return onErrorGotoLabelToLineNumber [ errorHandlerLabelForTheResumeStatement ] ;
292
280
}
293
281
//Resume <label>
294
- return DetermineLabeledExecutionBranchLine ( expression , labelIdLineNumberPairs ) ;
282
+ return labelIdLineNumberPairs [ resumeStmtExpression ] ;
295
283
}
296
284
297
- private static int DetermineLabeledExecutionBranchLine ( string expression , IEnumerable < ( string IdentifierName , int Line ) > IDandLinePairs )
298
- => int . TryParse ( expression , out var parsedLineNumber )
299
- ? parsedLineNumber
300
- : IDandLinePairs . Single ( v => v . IdentifierName . Equals ( expression ) ) . Line ;
285
+ private static bool IsBranchingOnErrorGoToLabel ( VBAParser . OnErrorStmtContext errorStmtCtxt )
286
+ {
287
+ var label = errorStmtCtxt . expression ( ) ? . GetText ( ) ;
288
+ if ( string . IsNullOrEmpty ( label ) )
289
+ {
290
+ return false ;
291
+ }
292
+ //The VBE will complain about labels other than:
293
+ //1. Numerics less than int.MaxValue (VBA: 'Long' max value). '0' returns false because it cause a branch
294
+ //2. Or, Any alphanumeric string beginning with a letter (VBE or the Debugger will choke on special characters, spaces, etc).
295
+ return ! ( int . TryParse ( label , out var numberLabel ) && numberLabel <= 0 ) ;
296
+ }
301
297
298
+ //TODO: Add IsStatic member to VariableDeclaration
302
299
private static bool IsStatic ( Declaration declaration )
303
300
{
304
301
var ctxt = declaration . Context . GetAncestor < VBAParser . VariableStmtContext > ( ) ;
0 commit comments