Skip to content

Commit

Permalink
Merge pull request #4457 from comintern/quickfixes
Browse files Browse the repository at this point in the history
Quick quick-fix fixes
  • Loading branch information
retailcoder committed Oct 26, 2018
2 parents 711c55d + 80dadd4 commit ca8beff
Show file tree
Hide file tree
Showing 4 changed files with 290 additions and 25 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,8 @@ public override void Fix(IInspectionResult result)
var rewriter = _state.GetRewriter(referenceResult.QualifiedName);

var setStatement = referenceResult.Context.GetAncestor<VBAParser.SetStmtContext>();
if (setStatement == null)
var isArgument = referenceResult.Context.GetAncestor<VBAParser.ArgumentContext>() != null;
if (setStatement == null || isArgument)
{
// Sheet accessed inline

Expand All @@ -49,20 +50,23 @@ public override void Fix(IInspectionResult result)
return moduleBodyElement != null && moduleBodyElement == referenceResult.Context.GetAncestor<VBAParser.ModuleBodyElementContext>();
});

var variableListContext = (VBAParser.VariableListStmtContext)sheetDeclaration.Context.Parent;
if (variableListContext.variableSubStmt().Length == 1)
if (!sheetDeclaration.IsUndeclared)
{
rewriter.Remove(variableListContext.Parent as ParserRuleContext);
}
else if (sheetDeclaration.Context == variableListContext.variableSubStmt().Last())
{
rewriter.Remove(variableListContext.COMMA().Last());
rewriter.Remove(sheetDeclaration);
}
else
{
rewriter.Remove(variableListContext.COMMA().First(comma => comma.Symbol.StartIndex > sheetDeclaration.Context.Start.StartIndex));
rewriter.Remove(sheetDeclaration);
var variableListContext = (VBAParser.VariableListStmtContext)sheetDeclaration.Context.Parent;
if (variableListContext.variableSubStmt().Length == 1)
{
rewriter.Remove(variableListContext.Parent as ParserRuleContext);
}
else if (sheetDeclaration.Context == variableListContext.variableSubStmt().Last())
{
rewriter.Remove(variableListContext.COMMA().Last());
rewriter.Remove(sheetDeclaration);
}
else
{
rewriter.Remove(variableListContext.COMMA().First(comma => comma.Symbol.StartIndex > sheetDeclaration.Context.Start.StartIndex));
rewriter.Remove(sheetDeclaration);
}
}

foreach (var reference in sheetDeclaration.References)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
using Antlr4.Runtime.Misc;
using Rubberduck.Common;
using Rubberduck.Interaction;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Rewriter;
using Rubberduck.Parsing.Symbols;
Expand Down Expand Up @@ -152,7 +153,12 @@ private void UpdateOtherModules()

private void InsertNewDeclaration()
{
var newVariable = $"Dim {_target.IdentifierName} As {_target.AsTypeName}{Environment.NewLine}";
var subscripts = _target.Context.GetDescendent<VBAParser.SubscriptsContext>()?.GetText() ?? string.Empty;
var identifier = _target.IsArray ? $"{_target.IdentifierName}({subscripts})" : _target.IdentifierName;

var newVariable = _target.AsTypeContext is null
? $"{Tokens.Dim} {identifier} {Tokens.As} {Tokens.Variant}{Environment.NewLine}"
: $"{Tokens.Dim} {identifier} {Tokens.As} {(_target.IsSelfAssigned ? Tokens.New + " " : string.Empty)}{_target.AsTypeNameWithoutArrayDesignator}{Environment.NewLine}";

var firstReference = _target.References.OrderBy(r => r.Selection.StartLine).First();

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -276,6 +276,88 @@ End Sub
}
}

[Test]
[Category("QuickFixes")]
public void SheetAccessedUsingString_QuickFixWorks_TransientReferenceSetStatement()
{
const string inputCode = @"
Sub Test()
Dim ws As Worksheet
Set ws = Worksheets.Add(Worksheets(""Sheet1""))
Debug.Print ws.Name
End Sub";

const string expectedCode = @"
Sub Test()
Dim ws As Worksheet
Set ws = Worksheets.Add(Sheet1)
Debug.Print ws.Name
End Sub";

using (var state = ArrangeParserAndParse(inputCode, out var component))
{
var inspection = new SheetAccessedUsingStringInspection(state);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

new AccessSheetUsingCodeNameQuickFix(state).Fix(inspectionResults.First());
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
}
}

[Test]
[Category("QuickFixes")]
public void SheetAccessedUsingString_QuickFixWorks_TransientReferenceNoSetStatement()
{
const string inputCode = @"
Sub Test()
If Not Worksheets.Add(Worksheets(""Sheet1"")) Is Nothing Then
Debug.Print ""Added""
End If
End Sub";

const string expectedCode = @"
Sub Test()
If Not Worksheets.Add(Sheet1) Is Nothing Then
Debug.Print ""Added""
End If
End Sub";

using (var state = ArrangeParserAndParse(inputCode, out var component))
{
var inspection = new SheetAccessedUsingStringInspection(state);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

new AccessSheetUsingCodeNameQuickFix(state).Fix(inspectionResults.First());
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
}
}

[Test]
[Category("QuickFixes")]
public void SheetAccessedUsingString_QuickFixWorks_ImplicitVariableAssignment()
{
const string inputCode = @"
Sub Test()
Set ws = Worksheets(""Sheet1"")
ws.Name = ""Foo""
End Sub";

const string expectedCode = @"
Sub Test()
Sheet1.Name = ""Foo""
End Sub";

using (var state = ArrangeParserAndParse(inputCode, out var component))
{
var inspection = new SheetAccessedUsingStringInspection(state);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

new AccessSheetUsingCodeNameQuickFix(state).Fix(inspectionResults.First());
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
}
}

private static RubberduckParserState ArrangeParserAndParse(string inputCode, out IVBComponent component)
{
var builder = new MockVbeBuilder();
Expand Down

0 comments on commit ca8beff

Please sign in to comment.