Skip to content

Commit

Permalink
Merge pull request #4467 from comintern/quickfixes
Browse files Browse the repository at this point in the history
More quickfix bug fixes
  • Loading branch information
retailcoder committed Oct 29, 2018
2 parents 46cdca5 + 68855f6 commit 0aaf7c1
Show file tree
Hide file tree
Showing 5 changed files with 128 additions and 8 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
.Where(declaration =>
!declaration.IsWithEvents
&& !IsIgnoringInspectionResultFor(declaration, AnnotationName)
&& declaration.References.All(reference => reference.IsAssignment));
&& !declaration.References.Any());

return declarations.Select(issue =>
new DeclarationInspectionResult(this,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ internal class IdentifierReferenceInspectionResult : InspectionResultBase
private static QualifiedMemberName? GetQualifiedMemberName(RubberduckParserState state, IdentifierReference reference)
{
var members = state.DeclarationFinder.Members(reference.QualifiedModuleName);
return members.SingleOrDefault(m => m.Selection.Contains(reference.Selection))?.QualifiedName;
return members.SingleOrDefault(m => reference.Context.IsDescendentOf(m.Context))?.QualifiedName;
}
}
}
Original file line number Diff line number Diff line change
@@ -1,10 +1,12 @@
using System;
using System.Collections.Generic;
using System.Linq;
using Antlr4.Runtime;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Concrete;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;

namespace Rubberduck.Inspections.QuickFixes
Expand All @@ -23,8 +25,26 @@ public override void Fix(IInspectionResult result)
{
var rewriter = _state.GetRewriter(result.QualifiedSelection.QualifiedName);

if (result.Context.Parent.Parent is VBAParser.WithStmtContext withContext)
{
var lines = withContext.GetText().Replace("\r", string.Empty).Split('\n');
// Assume that the End With is at the appropriate indentation level for the block. Note that this could
// over-indent or under-indent some lines if statement separators are being used, but meh.
var padding = new string(' ', lines.Last().IndexOf(Tokens.End, StringComparison.Ordinal));

var replacement = new List<string>
{
$"{Tokens.CommentMarker}TODO - {result.Description}",
$"{Tokens.CommentMarker}{padding}{lines.First()}"
};
replacement.AddRange(lines.Skip(1)
.Select(line => Tokens.CommentMarker + line));

rewriter.Replace(withContext, string.Join(Environment.NewLine, replacement));
return;
}
var assignmentContext = result.Context.GetAncestor<VBAParser.LetStmtContext>() ??
(ParserRuleContext)result.Context.GetAncestor<VBAParser.CallStmtContext>();
(ParserRuleContext)result.Context.GetAncestor<VBAParser.CallStmtContext>();

rewriter.Remove(assignmentContext);
}
Expand Down
20 changes: 16 additions & 4 deletions RubberduckTests/Inspections/VariableNotUsedInspectionTests.cs
Original file line number Diff line number Diff line change
Expand Up @@ -148,12 +148,24 @@ public void VariableNotUsed_DoesNotReturnsResult_UsedInNameStatement()

[Test]
[Category("Inspections")]
public void InspectionName()
public void VariableUsed_DoesNotReturnResultIfAssigned()
{
const string inspectionName = "VariableNotUsedInspection";
var inspection = new VariableNotUsedInspection(null);
const string inputCode =
@"Function Foo() As Boolean
Dim var1 as String
var1 = ""test""
End Function";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
using (var state = MockParser.CreateAndParse(vbe.Object))
{

var inspection = new VariableNotUsedInspection(state);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

Assert.AreEqual(inspectionName, inspection.Name);
Assert.AreEqual(0, inspectionResults.Count());
}
}

}
}
Original file line number Diff line number Diff line change
Expand Up @@ -39,5 +39,93 @@ public void UnassignedVariableUsage_QuickFixWorks()
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
}
}

// See https://github.com/rubberduck-vba/Rubberduck/issues/3636
[Test]
[Category("QuickFixes")]
public void UnassignedVariableUsage_QuickFixWorksWithBlock()
{
const string inputCode =
@"Sub test()
Dim wb As Workbook
With wb
Debug.Print .Name
Debug.Print .Name
Debug.Print .Name
End With
End Sub";

const string expectedCode =
@"Sub test()
Dim wb As Workbook
'TODO - {0}
' With wb
' Debug.Print .Name
' Debug.Print .Name
' Debug.Print .Name
' End With
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component);
using (var state = MockParser.CreateAndParse(vbe.Object))
{
var inspection = new UnassignedVariableUsageInspection(state);
var inspectionResult = inspection.GetInspectionResults(CancellationToken.None).First();
var expected = string.Format(expectedCode, inspectionResult.Description);

new RemoveUnassignedVariableUsageQuickFix(state).Fix(inspectionResult);
var actual = state.GetRewriter(component).GetText();
Assert.AreEqual(expected, actual);
}
}

[Test]
[Ignore("Passes when run individually, does not pass when all tests are run.")]
[Category("QuickFixes")]
public void UnassignedVariableUsage_QuickFixWorksNestedWithBlock()
{
const string inputCode =
@"Sub test()
Dim wb As Workbook
Set wb = ThisWorkbook
Dim ws As Worksheet
With wb
Debug.Print .Name
With ws
Debug.Print .Name
Debug.Print .Name
Debug.Print .Name
End With
End With
End Sub";

const string expectedCode =
@"Sub test()
Dim wb As Workbook
Set wb = ThisWorkbook
Dim ws As Worksheet
With wb
Debug.Print .Name
'TODO - {0}
' With ws
' Debug.Print .Name
' Debug.Print .Name
' Debug.Print .Name
' End With
End With
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component);
using (var state = MockParser.CreateAndParse(vbe.Object))
{
var inspection = new UnassignedVariableUsageInspection(state);
var inspectionResult = inspection.GetInspectionResults(CancellationToken.None).First();
var expected = string.Format(expectedCode, inspectionResult.Description);

new RemoveUnassignedVariableUsageQuickFix(state).Fix(inspectionResult);
var actual = state.GetRewriter(component).GetText();
Assert.AreEqual(expected, actual);
}
}
}
}

0 comments on commit 0aaf7c1

Please sign in to comment.