@@ -101,7 +101,7 @@ private static List<IdentifierReference> UnusedAssignmentReferences(INode node)
101
101
protected override bool IsResultReference ( IdentifierReference reference , DeclarationFinder finder )
102
102
{
103
103
return ! ( IsAssignmentOfNothing ( reference )
104
- || IsPotentiallyUsedViaResumeOrGoToExecutionBranch ( reference , finder ) ) ;
104
+ || IsPotentiallyUsedViaJump ( reference , finder ) ) ;
105
105
}
106
106
107
107
private static bool IsAssignmentOfNothing ( IdentifierReference reference )
@@ -116,134 +116,136 @@ private static bool IsAssignmentOfNothing(IdentifierReference reference)
116
116
/// An ErrorHandler block that branches execution to a location where the asignment may be used.
117
117
/// </summary>
118
118
/// <remarks>
119
- /// Excludes Assignment references that meet the following conditions:
120
- /// 1. Preceed a GoTo or Resume statement that branches execution to a line before the
119
+ /// Filters Assignment references that meet the following conditions:
120
+ /// 1. Precedes a GoTo or Resume statement that branches execution to a line before the
121
121
/// assignment reference, and
122
122
/// 2. A non-assignment reference is present on a line that is:
123
123
/// a) At or below the start of the execution branch, and
124
124
/// b) Above the next ExitStatement line (if one exists) or the end of the procedure
125
125
/// </remarks>
126
- /// <param name="resultCandidate"></param>
127
- /// <param name="finder"></param>
128
- /// <returns></returns>
129
- private static bool IsPotentiallyUsedViaResumeOrGoToExecutionBranch ( IdentifierReference resultCandidate , DeclarationFinder finder )
126
+ private static bool IsPotentiallyUsedViaJump ( IdentifierReference resultCandidate , DeclarationFinder finder )
130
127
{
131
128
if ( ! resultCandidate . Declaration . References . Any ( rf => ! rf . IsAssignment ) ) { return false ; }
132
129
133
130
var labelIdLineNumberPairs = finder . DeclarationsWithType ( DeclarationType . LineLabel )
134
131
. Where ( label => resultCandidate . ParentScoping . Equals ( label . ParentDeclaration ) )
135
132
. Select ( lbl => ( lbl . IdentifierName , lbl . Context . Start . Line ) ) ;
136
133
137
- return GotoExecutionBranchPotentiallyUsesVariable ( resultCandidate , labelIdLineNumberPairs )
138
- || ResumeExecutionBranchPotentiallyUsesVariable ( resultCandidate , labelIdLineNumberPairs ) ;
134
+ return GotoPotentiallyUsesVariable ( resultCandidate , labelIdLineNumberPairs )
135
+ || ResumePotentiallyUsesVariable ( resultCandidate , labelIdLineNumberPairs ) ;
139
136
}
140
137
141
- private static bool GotoExecutionBranchPotentiallyUsesVariable ( IdentifierReference resultCandidate , IEnumerable < ( string , int ) > labelIdLineNumberPairs )
138
+ private static bool GotoPotentiallyUsesVariable ( IdentifierReference resultCandidate , IEnumerable < ( string , int ) > labelIdLineNumberPairs )
142
139
{
143
- var gotoCtxts = resultCandidate . ParentScoping . Context . GetDescendents < VBAParser . GoToStmtContext > ( )
144
- . Where ( gotoCtxt => gotoCtxt . Start . Line > resultCandidate . Context . Start . Line ) ;
145
-
146
- if ( ! gotoCtxts . Any ( ) ) { return false ; }
147
-
148
- var gotoStmt = GetFirstContextAfterLine ( gotoCtxts , resultCandidate . Context . Start . Line ) ;
149
-
150
- if ( gotoStmt == null ) { return false ; }
151
-
152
- var executionBranchLine = DetermineExecutionBranchLine ( gotoStmt . expression ( ) . GetText ( ) , labelIdLineNumberPairs ) ;
140
+ if ( TryGetRelevantJumpContext < VBAParser . GoToStmtContext > ( resultCandidate , out var gotoStmt ) )
141
+ {
142
+ return IsPotentiallyUsedAssignment ( gotoStmt , resultCandidate , labelIdLineNumberPairs ) ;
143
+ }
153
144
154
- return IsPotentiallyUsedAssignment ( resultCandidate , executionBranchLine ) ;
145
+ return false ;
155
146
}
156
147
157
- private static bool ResumeExecutionBranchPotentiallyUsesVariable ( IdentifierReference resultCandidate , IEnumerable < ( string IdentifierName , int Line ) > labelIdLineNumberPairs )
148
+ private static bool ResumePotentiallyUsesVariable ( IdentifierReference resultCandidate , IEnumerable < ( string IdentifierName , int Line ) > labelIdLineNumberPairs )
158
149
{
159
- var resumeStmtCtxts = resultCandidate . ParentScoping . Context . GetDescendents < VBAParser . ResumeStmtContext > ( )
160
- . Where ( jumpCtxt => jumpCtxt . Start . Line > resultCandidate . Context . Start . Line ) ;
161
-
162
- if ( ! resumeStmtCtxts . Any ( ) ) { return false ; }
163
-
164
- var onErrorGotoStatements = resultCandidate . ParentScoping . Context . GetDescendents < VBAParser . OnErrorStmtContext > ( )
165
- . Where ( errorStmtCtxt => ! errorStmtCtxt . expression ( ) . GetText ( ) . Equals ( "0" ) )
166
- . ToDictionary ( k => k . expression ( ) ? . GetText ( ) ?? "0" , v => v . Start . Line ) ;
167
-
168
- var errorHandlerLabelsAndLines = labelIdLineNumberPairs . Where ( pair => onErrorGotoStatements . ContainsKey ( pair . IdentifierName ) ) ;
169
-
170
- //If the resultCandidate line preceeds all ErrorHandlers/Resume statements - it is not evaluated
171
- if ( errorHandlerLabelsAndLines . All ( s => s . Line > resultCandidate . Context . Start . Line ) )
150
+ if ( TryGetRelevantJumpContext < VBAParser . ResumeStmtContext > ( resultCandidate , out var resumeStmt ) )
172
151
{
173
- return false ;
152
+ return IsPotentiallyUsedAssignment ( resumeStmt , resultCandidate , labelIdLineNumberPairs ) ;
174
153
}
175
154
176
- var resumeStmt = GetFirstContextAfterLine ( resumeStmtCtxts , resultCandidate . Context . Start . Line ) ;
155
+ return false ;
156
+ }
177
157
178
- if ( resumeStmt == null ) { return false ; }
158
+ private static bool TryGetRelevantJumpContext < T > ( IdentifierReference resultCandidate , out T ctxt ) where T : ParserRuleContext //, IEnumerable<T> stmtContexts, int targetLine, int? targetColumn = null) where T : ParserRuleContext
159
+ {
160
+ ctxt = resultCandidate . ParentScoping . Context . GetDescendents < T > ( )
161
+ . Where ( sc => sc . Start . Line > resultCandidate . Context . Start . Line
162
+ || ( sc . Start . Line == resultCandidate . Context . Start . Line
163
+ && sc . Start . Column > resultCandidate . Context . Start . Column ) )
164
+ . OrderBy ( sc => sc . Start . Line - resultCandidate . Context . Start . Line )
165
+ . ThenBy ( sc => sc . Start . Column - resultCandidate . Context . Start . Column )
166
+ . FirstOrDefault ( ) ;
167
+ return ctxt != null ;
168
+ }
179
169
170
+ private static bool IsPotentiallyUsedAssignment < T > ( T jumpContext , IdentifierReference resultCandidate , IEnumerable < ( string , int ) > labelIdLineNumberPairs ) //, int executionBranchLine)
171
+ {
180
172
int ? executionBranchLine = null ;
181
-
182
- var expression = resumeStmt . expression ( ) ? . GetText ( ) ;
183
-
184
- //For Resume and Resume Next, expression() is null
185
- if ( string . IsNullOrEmpty ( expression ) )
173
+ if ( jumpContext is VBAParser . GoToStmtContext gotoCtxt )
186
174
{
187
- //Get info for the errorHandlerLabel above the Resume statement
188
- ( string IdentifierName , int Line ) ? errorHandlerLabel = labelIdLineNumberPairs
189
- . Where ( pair => resumeStmt . Start . Line > pair . Line )
190
- . OrderBy ( pair => resumeStmt . Start . Line - pair . Line )
191
- . FirstOrDefault ( ) ;
192
-
193
- //Since the execution branch line for Resume and Resume Next statements
194
- //is indeterminant by static analysis, the On***GoTo statement
195
- //is used as the execution branch line
196
- if ( errorHandlerLabel . HasValue && onErrorGotoStatements . ContainsKey ( errorHandlerLabel . Value . IdentifierName ) )
197
- {
198
- executionBranchLine = onErrorGotoStatements [ errorHandlerLabel . Value . IdentifierName ] ;
199
- }
175
+ executionBranchLine = DetermineLabeledExecutionBranchLine ( gotoCtxt . expression ( ) . GetText ( ) , labelIdLineNumberPairs ) ;
200
176
}
201
177
else
202
178
{
203
- executionBranchLine = DetermineExecutionBranchLine ( expression , labelIdLineNumberPairs ) ;
179
+ executionBranchLine = DetermineResumeStmtExecutionBranchLine ( jumpContext as VBAParser . ResumeStmtContext , resultCandidate , labelIdLineNumberPairs ) ;
204
180
}
205
181
206
182
return executionBranchLine . HasValue
207
- ? IsPotentiallyUsedAssignment ( resultCandidate , executionBranchLine . Value )
208
- : false ;
183
+ ? AssignmentIsUsedPriorToExitStmts ( resultCandidate , executionBranchLine . Value )
184
+ : false ;
209
185
}
210
186
211
- private static bool IsPotentiallyUsedAssignment ( IdentifierReference resultCandidate , int executionBranchLine )
187
+ private static bool AssignmentIsUsedPriorToExitStmts ( IdentifierReference resultCandidate , int executionBranchLine )
212
188
{
213
- if ( resultCandidate . Context . Start . Line <= executionBranchLine ) { return false ; }
189
+ if ( resultCandidate . Context . Start . Line < executionBranchLine ) { return false ; }
214
190
215
- var exitStmtCtxts = resultCandidate . ParentScoping . Context . GetDescendents < VBAParser . ExitStmtContext > ( )
216
- . Where ( exitCtxt => exitCtxt . Start . Line > executionBranchLine
217
- && exitCtxt . EXIT_DO ( ) == null
218
- && exitCtxt . EXIT_FOR ( ) == null ) ;
191
+ var procedureExitStmtCtxts = resultCandidate . ParentScoping . Context . GetDescendents < VBAParser . ExitStmtContext > ( )
192
+ . Where ( exitCtxt => exitCtxt . EXIT_DO ( ) == null
193
+ && exitCtxt . EXIT_FOR ( ) == null ) ;
219
194
220
- var exitStmtCtxt = GetFirstContextAfterLine ( exitStmtCtxts , executionBranchLine ) ;
195
+ var nonAssignmentCtxts = resultCandidate . Declaration . References
196
+ . Where ( rf => ! rf . IsAssignment )
197
+ . Select ( rf => rf . Context ) ;
221
198
222
- var nonAssignmentReferences = resultCandidate . Declaration . References
223
- . Where ( rf => ! rf . IsAssignment ) ;
199
+ var sortedContextsAfterBranch = nonAssignmentCtxts . Concat ( procedureExitStmtCtxts )
200
+ . Where ( ctxt => ctxt . Start . Line >= executionBranchLine )
201
+ . OrderBy ( ctxt => ctxt . Start . Line )
202
+ . ThenBy ( ctxt => ctxt . Start . Column ) ;
224
203
225
- var possibleUse = exitStmtCtxt != null
226
- ? nonAssignmentReferences . Where ( rf => rf . Context . Start . Line >= executionBranchLine
227
- && rf . Context . Start . Line < exitStmtCtxt . Start . Line )
228
- : nonAssignmentReferences . Where ( rf => rf . Context . Start . Line >= executionBranchLine ) ;
229
-
230
- return possibleUse . Any ( ) ;
204
+ return ! ( sortedContextsAfterBranch . FirstOrDefault ( ) is VBAParser . ExitStmtContext ) ;
231
205
}
232
206
233
- private static int DetermineExecutionBranchLine ( string expression , IEnumerable < ( string IdentifierName , int Line ) > IDandLinePairs )
207
+ private static int ? DetermineResumeStmtExecutionBranchLine ( VBAParser . ResumeStmtContext resumeStmt , IdentifierReference resultCandidate , IEnumerable < ( string IdentifierName , int Line ) > labelIdLineNumberPairs ) //where T: ParserRuleContext
234
208
{
235
- if ( int . TryParse ( expression , out var parsedLineNumber ) )
209
+ var onErrorGotoLabelToLineNumber = resultCandidate . ParentScoping . Context . GetDescendents < VBAParser . OnErrorStmtContext > ( )
210
+ . Where ( errorStmtCtxt => ! errorStmtCtxt . expression ( ) . GetText ( ) . Equals ( "0" ) )
211
+ . ToDictionary ( k => k . expression ( ) ? . GetText ( ) ?? "No Label" , v => v . Start . Line ) ;
212
+
213
+ var errorHandlerLabelsAndLines = labelIdLineNumberPairs
214
+ . Where ( pair => onErrorGotoLabelToLineNumber . ContainsKey ( pair . IdentifierName ) ) ;
215
+
216
+ //Labels must be located at the start of a line.
217
+ //If the resultCandidate line precedes all error handling related labels,
218
+ //a Resume statement cannot be invoked (successfully) for the resultCandidate
219
+ if ( ! errorHandlerLabelsAndLines . Any ( s => s . Line <= resultCandidate . Context . Start . Line ) )
236
220
{
237
- return parsedLineNumber ;
221
+ return null ;
222
+ }
223
+
224
+ var expression = resumeStmt . expression ( ) ? . GetText ( ) ;
225
+
226
+ //For Resume and Resume Next, expression() is null
227
+ if ( string . IsNullOrEmpty ( expression ) )
228
+ {
229
+ //Get errorHandlerLabel for the Resume statement
230
+ string errorHandlerLabel = errorHandlerLabelsAndLines
231
+ . Where ( pair => resumeStmt . Start . Line >= pair . Line )
232
+ . OrderBy ( pair => resumeStmt . Start . Line - pair . Line )
233
+ . Select ( pair => pair . IdentifierName )
234
+ . FirstOrDefault ( ) ;
235
+
236
+ //Since the execution branch line for Resume and Resume Next statements
237
+ //is indeterminant by static analysis, the On***GoTo statement
238
+ //is used as the execution branch line
239
+ return onErrorGotoLabelToLineNumber [ errorHandlerLabel ] ;
238
240
}
239
- ( string label , int lineNumber ) = IDandLinePairs . Where ( v => v . IdentifierName . Equals ( expression ) ) . Single ( ) ;
240
- return lineNumber ;
241
+ //Resume < label>
242
+ return DetermineLabeledExecutionBranchLine ( expression , labelIdLineNumberPairs ) ;
241
243
}
242
244
243
- private static T GetFirstContextAfterLine < T > ( IEnumerable < T > stmtContexts , int targetLine ) where T : ParserRuleContext
244
- => stmtContexts . Where ( sc => sc . Start . Line > targetLine )
245
- . OrderBy ( sc => sc . Start . Line - targetLine )
246
- . FirstOrDefault ( ) ;
245
+ private static int DetermineLabeledExecutionBranchLine ( string expression , IEnumerable < ( string IdentifierName , int Line ) > IDandLinePairs )
246
+ => int . TryParse ( expression , out var parsedLineNumber )
247
+ ? parsedLineNumber
248
+ : IDandLinePairs . Single ( v => v . IdentifierName . Equals ( expression ) ) . Line ;
247
249
248
250
protected override string ResultDescription ( IdentifierReference reference )
249
251
{
0 commit comments