Skip to content

Commit 7079946

Browse files
committed
Quick fix works for interfaces
1 parent 4ee1d44 commit 7079946

File tree

3 files changed

+125
-11
lines changed

3 files changed

+125
-11
lines changed

RetailCoder.VBE/Inspections/ParameterCanBeByValInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
6060
{
6161
if (parametersAreByRef[i])
6262
{
63-
issues.Add(new ParameterCanBeByValInspectionResult(this, declarationParameters[i],
63+
issues.Add(new ParameterCanBeByValInspectionResult(this, State, declarationParameters[i],
6464
declarationParameters[i].Context, declarationParameters[i].QualifiedName));
6565
}
6666
}
@@ -88,7 +88,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
8888
&& ((VBAParser.ArgContext)declaration.Context).BYVAL() == null
8989
&& !IsUsedAsByRefParam(declarations, declaration)
9090
&& !declaration.References.Any(reference => reference.IsAssignment))
91-
.Select(issue => new ParameterCanBeByValInspectionResult(this, issue, issue.Context, issue.QualifiedName)));
91+
.Select(issue => new ParameterCanBeByValInspectionResult(this, State, issue, issue.Context, issue.QualifiedName)));
9292

9393
return issues;
9494
}
Lines changed: 58 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,11 @@
11
using System.Collections.Generic;
2+
using System.Linq;
23
using Antlr4.Runtime;
4+
using Rubberduck.Common;
5+
using Rubberduck.Parsing;
36
using Rubberduck.Parsing.Grammar;
47
using Rubberduck.Parsing.Symbols;
8+
using Rubberduck.Parsing.VBA;
59
using Rubberduck.VBEditor;
610

711
namespace Rubberduck.Inspections
@@ -10,12 +14,12 @@ public class ParameterCanBeByValInspectionResult : InspectionResultBase
1014
{
1115
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
1216

13-
public ParameterCanBeByValInspectionResult(IInspection inspection, Declaration target, ParserRuleContext context, QualifiedMemberName qualifiedName)
17+
public ParameterCanBeByValInspectionResult(IInspection inspection, RubberduckParserState state, Declaration target, ParserRuleContext context, QualifiedMemberName qualifiedName)
1418
: base(inspection, qualifiedName.QualifiedModuleName, context, target)
1519
{
1620
_quickFixes = new CodeInspectionQuickFix[]
1721
{
18-
new PassParameterByValueQuickFix(Context, QualifiedSelection),
22+
new PassParameterByValueQuickFix(state, Target, Context, QualifiedSelection),
1923
new IgnoreOnceQuickFix(Context, QualifiedSelection, inspection.AnnotationName)
2024
};
2125
}
@@ -30,21 +34,66 @@ public override string Description
3034

3135
public class PassParameterByValueQuickFix : CodeInspectionQuickFix
3236
{
33-
public PassParameterByValueQuickFix(ParserRuleContext context, QualifiedSelection selection)
37+
private readonly RubberduckParserState _state;
38+
private readonly Declaration _target;
39+
40+
public PassParameterByValueQuickFix(RubberduckParserState state, Declaration target, ParserRuleContext context, QualifiedSelection selection)
3441
: base(context, selection, InspectionsUI.PassParameterByValueQuickFix)
3542
{
43+
_state = state;
44+
_target = target;
3645
}
3746

3847
public override void Fix()
3948
{
40-
var selection = Selection.Selection;
41-
var selectionLength = ((VBAParser.ArgContext) Context).BYREF() == null ? 0 : 6;
49+
if (!_state.AllUserDeclarations.FindInterfaceMembers().Contains(_target.ParentDeclaration))
50+
{
51+
FixMethod((VBAParser.ArgContext) Context, Selection);
52+
}
53+
else
54+
{
55+
var declarationParameters =
56+
_state.AllUserDeclarations.Where(declaration => declaration.DeclarationType == DeclarationType.Parameter &&
57+
declaration.ParentDeclaration == _target.ParentDeclaration)
58+
.OrderBy(o => o.Selection.StartLine)
59+
.ThenBy(t => t.Selection.StartColumn)
60+
.ToList();
61+
62+
var parameterIndex = declarationParameters.IndexOf(_target);
63+
64+
if (parameterIndex == -1)
65+
{
66+
return; // should only happen if the parse results are stale; prevents a crash in that case
67+
}
68+
69+
var implementations = _state.AllUserDeclarations.FindInterfaceImplementationMembers(_target.ParentDeclaration);
70+
foreach (var member in implementations)
71+
{
72+
var parameters =
73+
_state.AllUserDeclarations.Where(declaration => declaration.DeclarationType == DeclarationType.Parameter &&
74+
declaration.ParentDeclaration == member)
75+
.OrderBy(o => o.Selection.StartLine)
76+
.ThenBy(t => t.Selection.StartColumn)
77+
.ToList();
78+
79+
FixMethod((VBAParser.ArgContext) parameters[parameterIndex].Context,
80+
parameters[parameterIndex].QualifiedSelection);
81+
}
82+
83+
FixMethod((VBAParser.ArgContext) declarationParameters[parameterIndex].Context,
84+
declarationParameters[parameterIndex].QualifiedSelection);
85+
}
86+
}
87+
88+
private void FixMethod(VBAParser.ArgContext context, QualifiedSelection qualifiedSelection)
89+
{
90+
var selectionLength = context.BYREF() == null ? 0 : 6;
4291

43-
var module = Selection.QualifiedName.Component.CodeModule;
44-
var lines = module.Lines[selection.StartLine, 1];
92+
var module = qualifiedSelection.QualifiedName.Component.CodeModule;
93+
var lines = module.Lines[context.Start.Line, 1];
4594

46-
var result = lines.Remove(selection.StartColumn - 1, selectionLength).Insert(selection.StartColumn - 1, Tokens.ByVal + ' ');
47-
module.ReplaceLine(selection.StartLine, result);
95+
var result = lines.Remove(context.Start.Column, selectionLength).Insert(context.Start.Column, Tokens.ByVal + ' ');
96+
module.ReplaceLine(context.Start.Line, result);
4897
}
4998
}
5099
}

RubberduckTests/Inspections/ParameterCanBeByValInspectionTests.cs

Lines changed: 65 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -638,6 +638,71 @@ public void ParameterCanBeByVal_QuickFixWorks_PassedByRef_MultilineParameter()
638638
Assert.AreEqual(expectedCode, module.Lines());
639639
}
640640

641+
[TestMethod]
642+
public void ParameterCanBeByVal_InterfaceMember_MultipleParams_OneCanBeByVal_QuickFixWorks()
643+
{
644+
//Input
645+
const string inputCode1 =
646+
@"Public Sub DoSomething(ByRef a As Integer, ByRef b As Integer)
647+
End Sub";
648+
const string inputCode2 =
649+
@"Implements IClass1
650+
651+
Private Sub IClass1_DoSomething(ByRef a As Integer, ByRef b As Integer)
652+
b = 42
653+
End Sub";
654+
const string inputCode3 =
655+
@"Implements IClass1
656+
657+
Private Sub IClass1_DoSomething(ByRef a As Integer, ByRef b As Integer)
658+
End Sub";
659+
660+
//Expected
661+
const string expectedCode1 =
662+
@"Public Sub DoSomething(ByVal a As Integer, ByRef b As Integer)
663+
End Sub";
664+
const string expectedCode2 =
665+
@"Implements IClass1
666+
667+
Private Sub IClass1_DoSomething(ByVal a As Integer, ByRef b As Integer)
668+
b = 42
669+
End Sub";
670+
const string expectedCode3 =
671+
@"Implements IClass1
672+
673+
Private Sub IClass1_DoSomething(ByVal a As Integer, ByRef b As Integer)
674+
End Sub";
675+
676+
//Arrange
677+
var builder = new MockVbeBuilder();
678+
var project = builder.ProjectBuilder("TestProject1", vbext_ProjectProtection.vbext_pp_none)
679+
.AddComponent("IClass1", vbext_ComponentType.vbext_ct_ClassModule, inputCode1)
680+
.AddComponent("Class1", vbext_ComponentType.vbext_ct_ClassModule, inputCode2)
681+
.AddComponent("Class2", vbext_ComponentType.vbext_ct_ClassModule, inputCode3)
682+
.Build();
683+
684+
var module1 = project.Object.VBComponents.Item("IClass1").CodeModule;
685+
var module2 = project.Object.VBComponents.Item("Class1").CodeModule;
686+
var module3 = project.Object.VBComponents.Item("Class2").CodeModule;
687+
var vbe = builder.AddProject(project).Build();
688+
689+
var mockHost = new Mock<IHostApplication>();
690+
mockHost.SetupAllProperties();
691+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object, new Mock<ISinks>().Object));
692+
693+
parser.Parse(new CancellationTokenSource());
694+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
695+
696+
var inspection = new ParameterCanBeByValInspection(parser.State);
697+
var inspectionResults = inspection.GetInspectionResults();
698+
699+
inspectionResults.Single().QuickFixes.Single(s => s is PassParameterByValueQuickFix).Fix();
700+
701+
Assert.AreEqual(expectedCode1, module1.Lines());
702+
Assert.AreEqual(expectedCode2, module2.Lines());
703+
Assert.AreEqual(expectedCode3, module3.Lines());
704+
}
705+
641706
[TestMethod]
642707
[TestCategory("Inspections")]
643708
public void ParameterCanBeByVal_IgnoreQuickFixWorks()

0 commit comments

Comments
 (0)