Rubberduck
Rubberduck copied to clipboard
AssignmentNotUsed Inspection false positive
Rubberduck version information Version 2.5.2.5906 OS: Microsoft Windows NT 10.0.19045.0, x64 Host Product: Microsoft Office 2016 x64 Host Version: 16.0.5404.1000 Host Executable: EXCEL.EXE
Description The code below generates AssignmentNotUsed warnings for the first assignement to previousColor, humanComment, expectedPart and colorPart, although all assignments after the first ones are conditional and the first assigned value may be (are) used afterward.
Private Sub processCell(ByVal cell As Range, ByVal rowDefaultColor As Long, Optional ByVal entry As Variant = Nothing)
Dim autoGeneratedComment As String
Dim previousColor As Long: previousColor = -1
' three parts of the comment
Dim humanComment As String: humanComment = ""
Dim expectedPart As String: expectedPart = ""
Dim colorPart As String: colorPart = ""
' parse existing comment
Dim result As Object
' Matches ReportParser comment alone or with human comment (group 0), with or witouht color info (group 1)
' No match means human comment alone
' SubMatches(0) is human added comment to be kept. Empty means no human addded comment, only ReportParser comment
' SubMatches(1) cell color prior to error to restore if error is fixed. Empty means no color information (restaure default color)
If Not cell.Comment Is Nothing Then
Set result = regexAutoComment.Execute(cell.Comment.text)
If result.Count <> 0 Then
' got a match, this means there is an auto generated part in this comment
If Not IsEmpty(result(0).SubMatches(0)) Then humanComment = result(0).SubMatches(0)
If Not IsEmpty(result(0).SubMatches(1)) Then previousColor = CLng(result(0).SubMatches(1))
humanComment = Utils.RemoveTrailingWhiteSpaces(humanComment)
Else
' No match -> the whole comment is human added, so we must keep it as it is
humanComment = cell.Comment.text
End If
End If
'''''''''''''''''''
' Stripped part with where previousColor, humanComment, expectedPart are read multiple times but never assigned
' + Some code where colorPart is conditionally assigned
'''''''''''''''''''
If humanComment <> "" And expectedPart <> "" Then
autoGeneratedComment = humanComment & vbNewLine & vbNewLine & expectedPart & colorPart
ElseIf humanComment <> "" And expectedPart = "" Then
autoGeneratedComment = humanComment
Else
autoGeneratedComment = expectedPart & colorPart
End If
''''''''''''''''''
' Stripped irrelevant code
''''''''''''''''''
End Sub
Expected behavior previousColor = -1, humanComment = "", expectedPart = "" and colorPart = "" should not be flagged as unused.
I can understand that explicitly assign "" to a newly declared string is useless and may generate a warning (but in my opinion it should not since it is making an implicit assignment explicit), but previousColor = -1 should definitily not trigger a warning
Additional context There is no jump in this sub, only If blocks so it not the same as #5456
I suppose this is linked somehow :
the following piece of code is extracted from https://codereview.stackexchange.com/q/156070
Dim Keys As Variant
Keys = this.Keys.Keys
Dim items As Variant
items = this.Keys.items
Dim nextkey As String
Dim nextIndex As Long
'Now decrement the indexes for all subsequent keys
For nextIndex = oneBasedIndex - 1 To this.Keys.Count - 1
nextkey = this.Keys.Keys(nextIndex)
this.Keys.Item(nextkey) = nextIndex + 1
items = this.Keys.items
Keys = this.Keys.Keys
Next nextIndex
AssignementNotUsed is triggered for "Keys" and "items" (as expected), but VariableNotUsed is also triggered for these two variables as well, which is not expected
but VariableNotUsed is also triggered for these two variables as well, which is not expected
The wording is difficult to nail right, but if that snippet is all there is to it, then VariableNotUsed is a correct diagnostic because while both are assigned, neither are being read - which is really what "not used" means in this context: the code would behave identically without these variables existing at all.
If there's other code underneath that snippet that reads Keys and items, then I'd be expecting AssignmentNotUsed to flag both initial assignments, and no results from VariableNotUsed.
I don't think the inspection is accounting for conditional re-assignments, and really it probably should. Excluding inspection results when an assignment is conditionally overwritten (parent context is a child of an "if" statement or block) would remove most of the false positive cases, I believe.
The wording is difficult to nail right, but if that snippet is all there is to it, then VariableNotUsed is a correct diagnostic because while both are assigned, neither are being read - which is really what "not used" means in this context: the code would behave identically without these variables existing at all.
In the second example, it is indeed unused. should have thought a little more before complaining ...
I don't think the inspection is accounting for conditional re-assignments, and really it probably should.
I wonder if there is more than that. Here is a snippet that I forgot to include in my first post after the second stripped part :
' colorize cell
If entry Is Nothing Then
' cell is not error
If previousColor >= 0 Then
' previous color was saved in comment, restore it
cell.Interior.color = previousColor
ElseIf cell.Interior.color = MRP_ERROR_COLOR Then
' no color was saved, apply default color
cell.Interior.color = rowDefaultColor
End If
Else
At the very end of the sub, I check wheter previousColor is positive or not, so the initial assignment to -1 is used, with or without conditional assignments. After reading your answer I thought that this access was ignored because it is conditional too. But even after removing the If entry Is Nothing Then block, previousColor is still marked as unused despite the access.
The problem seems to be that the inspection thinks that previousColor gets reassigned in the if block. It does not account for the fact that the assignment is not conditional. Accordingly, it complains that the first assignment is useless, which it is not.
This inspection was supposed to do proper code path analysis, but apparently, it fails at that.
@retailcoder Actually, if there was code using items and and Keys underneath the second example, AssignmentNotUsed should not flag the initial assignments, because the for loop might never run.
I don't know if this related but the following code also triggers the inspection
Option Explicit
Public Sub verifBug()
Dim lastColumn As Long
' retrieve requirements column
lastColumn = 1
Do Until IsEmpty(ActiveSheet.Cells(4, lastColumn))
lastColumn = lastColumn + 1
Loop
lastColumn = lastColumn + 1 ' triggers AssignmentNotUsed
Debug.Print "Last column is " & lastColumn
End Sub
What seems to confuse the parser is the Do Until loop: when I remove it the inspection warning is gone.
It's not exactly wrong: the value assigned by the last iteration of the loop is indeed overwritten before it's read. There should be a way to rephrase the loop (do...while?) such that lastColumn has the expected value when it exits.
That said, finding the last column of a range doesn't need a loop: the Range.End method behaves essentially like Ctrl+arrow navigation, so you can take a range at the far end of the worksheet and use .End(xlLeft) to get a range that's in the last column.
It's not exactly wrong: the value assigned by the last iteration of the loop is indeed overwritten before it's read.
Actually, it's not: the RHS is evaluated first, and should be counted as a read of the last assignment.
I believe the inspection might be having trouble with taking RHS into account in an expression like thing = thing + 1.
It's not exactly wrong: the value assigned by the last iteration of the loop is indeed overwritten before it's read.
Actually, it's not: the RHS is evaluated first, and should be counted as a read of the last assignment.
I believe the inspection might be having trouble with taking RHS into account in an expression like
thing = thing + 1.
It is indeed the last assignment that is flagged as not used, not the one in the loop. I don't want the last cell of the range but the second after it
I didn't thought about Range.End when I wrote the code (I don't think I was aware of its existence back then). Funnily enough, replacing the loop by Range.End() does not trigger the inspection, despite the last assignment being almost the same:
Public Sub verifBug()
Dim lastColumn As Long
lastColumn = 1
lastColumn = ActiveSheet.Cells(4, lastColumn).End(xlRight).column
lastColumn = lastColumn + 2 ' does not trigger AssignmentNotUsed
Debug.Print "Last column is " & lastColumn
End Sub
I also tried to still increment by 1 instead of 2 at the end, and the inspection is not triggered. But if i put the loop back in place, I get the warning.
(I know now that I also could use the one-liner lastColumn =ActiveSheet.Cells(4, 1).End(xlRight).Offset(0,2).column but I still wanted to test the parser bug)
There's definitely something weird going on that deserves attention, thanks for digging!
Don't know if this is related but the following code also triggers a false positive
Public Sub test()
Dim name As String
If ActiveSheet.name = "test" Then
name = sheet.name & " is test"
Debug.Print (name)
End If
name = sheet.name ' AssignmentNotUsed triggered here
Debug.Print (name)
End Sub
It's something with the assignment in the conditional if statement, commenting out the assignment in the If statement does not trigger the inspection.
IIRC Debug statements are a special case, they don't really exist so we're parsing them with specific grammar rules. Could be that the resolver is skipping over the arguments, since it's a special syntax and I'd have to check how it's handled specifically, but the context-sensitive toolbar label that we're [ab]using as a status bar gives a good insight on how Rubberduck understands the code: when you place the cursor/caret on the (name) argument (the parentheses are redundant btw) of the Debug.Print statement, if the status bar says you've selected the name local variable then the resolver is correctly picking up the identifier reference; if it says you're in a Debug.Print statement, it knows you're in the argument list of the statement, but didn't resolve the reference there.
Another way to verify would be to select the name declaration; the status bar should say it is referenced 4 times, and clicking that button (or right-clicking the variable and picking "find all references") should list all 4 instances; refactor/rename should correctly rename all of them... and then that would mean it's a problem with the inspection itself, rather than a resolution issue.
IIRC
Debugstatements are a special case, they don't really exist so we're parsing them with specific grammar rules. Could be that the resolver is skipping over the arguments, since it's a special syntax and I'd have to check how it's handled specifically, but the context-sensitive toolbar label that we're [ab]using as a status bar gives a good insight on how Rubberduck understands the code: when you place the cursor/caret on the(name)argument (the parentheses are redundant btw) of theDebug.Printstatement, if the status bar says you've selected thenamelocal variable then the resolver is correctly picking up the identifier reference; if it says you're in aDebug.Printstatement, it knows you're in the argument list of the statement, but didn't resolve the reference there. Another way to verify would be to select thenamedeclaration; the status bar should say it is referenced 4 times, and clicking that button (or right-clicking the variable and picking "find all references") should list all 4 instances; refactor/rename should correctly rename all of them... and then that would mean it's a problem with the inspection itself, rather than a resolution issue.
Yes the status bar says 4 references. The following code without Debug statements has the same issue:
Public Function getName() As String
Dim name As String
If ActiveSheet.name = "test" Then
name = ActiveSheet.name & " is test"
getName = name
Exit Function
End If
name = ActiveSheet.name ' AssignmentNotUsed triggered here
getName = name
End Function