Skip to content

Commit 0d46064

Browse files
committed
Add quick fix
1 parent 8b9ff10 commit 0d46064

File tree

8 files changed

+263
-45
lines changed

8 files changed

+263
-45
lines changed

Rubberduck.Inspections/Concrete/BooleanAssignedInIfElseInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ public sealed class BooleanAssignedInIfElseInspection : ParseTreeInspectionBase
1919
public BooleanAssignedInIfElseInspection(RubberduckParserState state)
2020
: base(state) { }
2121

22-
public override CodeInspectionType InspectionType => CodeInspectionType.LanguageOpportunities;
22+
public override CodeInspectionType InspectionType => CodeInspectionType.MaintainabilityAndReadabilityIssues;
2323

2424
public override IInspectionListener Listener { get; } =
2525
new BooleanAssignedInIfElseListener();
Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,46 @@
1+
using Rubberduck.Inspections.Abstract;
2+
using Rubberduck.Inspections.Concrete;
3+
using Rubberduck.Parsing.Grammar;
4+
using Rubberduck.Parsing.Inspections.Abstract;
5+
using Rubberduck.Parsing.Inspections.Resources;
6+
using Rubberduck.Parsing.Symbols;
7+
using Rubberduck.Parsing.VBA;
8+
9+
namespace Rubberduck.Inspections.QuickFixes
10+
{
11+
public sealed class ReplaceIfElseWithConditionalStatementQuickFix : QuickFixBase
12+
{
13+
private readonly RubberduckParserState _state;
14+
15+
public ReplaceIfElseWithConditionalStatementQuickFix(RubberduckParserState state)
16+
: base(typeof(BooleanAssignedInIfElseInspection))
17+
{
18+
_state = state;
19+
}
20+
21+
public override void Fix(IInspectionResult result)
22+
{
23+
var ifContext = (VBAParser.IfStmtContext) result.Context;
24+
var letStmt = ParserRuleContextHelper.GetDescendent<VBAParser.LetStmtContext>(ifContext.block());
25+
26+
var conditional = ifContext.booleanExpression().GetText();
27+
28+
if (letStmt.expression().GetText() == Tokens.False)
29+
{
30+
conditional = $"Not ({conditional})";
31+
}
32+
33+
var rewriter = _state.GetRewriter(result.QualifiedSelection.QualifiedName);
34+
rewriter.Replace(result.Context, $"{letStmt.lExpression().GetText()} = {conditional}");
35+
}
36+
37+
public override string Description(IInspectionResult result)
38+
{
39+
return InspectionsUI.ReplaceIfElseWithConditionalStatementQuickFix;
40+
}
41+
42+
public override bool CanFixInProcedure { get; } = true;
43+
public override bool CanFixInModule { get; } = true;
44+
public override bool CanFixInProject { get; } = true;
45+
}
46+
}

Rubberduck.Inspections/Rubberduck.Inspections.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -117,6 +117,7 @@
117117
<Compile Include="Concrete\ProcedureCanBeWrittenAsFunctionInspection.cs" />
118118
<Compile Include="Concrete\ProcedureNotUsedInspection.cs" />
119119
<Compile Include="Properties\AssemblyInfo.cs" />
120+
<Compile Include="QuickFixes\ReplaceIfElseWithConditionalStatementQuickFix.cs" />
120121
<Compile Include="QuickFixes\AddIdentifierToWhiteListQuickFix.cs" />
121122
<Compile Include="QuickFixes\ApplicationWorksheetFunctionQuickFix.cs" />
122123
<Compile Include="QuickFixes\AssignedByValParameterMakeLocalCopyQuickFix.cs" />

Rubberduck.Parsing/Inspections/Resources/InspectionsUI.resx

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
<?xml version="1.0" encoding="UTF-8"?>
1+
<?xml version="1.0" encoding="utf-8"?>
22
<root>
33
<!--
44
Microsoft ResX Schema
@@ -59,7 +59,7 @@
5959
: using a System.ComponentModel.TypeConverter
6060
: and then encoded with base64 encoding.
6161
-->
62-
<xsd:schema xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata" id="root">
62+
<xsd:schema id="root" xmlns="" xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata">
6363
<xsd:import namespace="http://www.w3.org/XML/1998/namespace" />
6464
<xsd:element name="root" msdata:IsDataSet="true">
6565
<xsd:complexType>
@@ -875,4 +875,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
875875
<data name="BooleanAssignedInIfElseInspectionResultFormat" xml:space="preserve">
876876
<value>Boolean literal '{0}' assigned in conditional</value>
877877
</data>
878+
<data name="ReplaceIfElseWithConditionalStatementQuickFix" xml:space="preserve">
879+
<value>Replace If/Else with single assignment</value>
880+
</data>
878881
</root>

Rubberduck.Parsing/Inspections/Resources/InspectionsUI1.Designer.cs

Lines changed: 47 additions & 38 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

RubberduckTests/Inspections/BooleanAssignedInIfElseInspectionTests.cs

Lines changed: 26 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,28 @@ If True Then
3232
Assert.AreEqual(1, results.Count());
3333
}
3434

35+
[TestMethod]
36+
[TestCategory("Inspections")]
37+
public void QualifiedName()
38+
{
39+
const string inputcode =
40+
@"Sub Foo()
41+
If True Then
42+
Fizz.Buzz = True
43+
Else
44+
Fizz.Buzz = False
45+
EndIf
46+
End Sub";
47+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputcode, out _);
48+
var state = MockParser.CreateAndParse(vbe.Object);
49+
50+
var inspection = new BooleanAssignedInIfElseInspection(state);
51+
var inspector = InspectionsHelper.GetInspector(inspection);
52+
var results = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
53+
54+
Assert.AreEqual(1, results.Count());
55+
}
56+
3557
[TestMethod]
3658
[TestCategory("Inspections")]
3759
public void MultipleResults()
@@ -181,7 +203,7 @@ If True Then
181203
public void IsIgnored()
182204
{
183205
const string inputcode =
184-
@"Sub Foo()
206+
@"Sub Foo()
185207
Dim d
186208
'@Ignore BooleanAssignedInIfElse
187209
If True Then
@@ -205,7 +227,7 @@ If True Then
205227
public void BlockContainsPrefixComment()
206228
{
207229
const string inputcode =
208-
@"Sub Foo()
230+
@"Sub Foo()
209231
Dim d
210232
If True Then
211233
' test
@@ -229,7 +251,7 @@ If True Then
229251
public void BlockContainsPostfixComment()
230252
{
231253
const string inputcode =
232-
@"Sub Foo()
254+
@"Sub Foo()
233255
Dim d
234256
If True Then
235257
d = True
@@ -253,7 +275,7 @@ If True Then
253275
public void BlockContainsEOLComment()
254276
{
255277
const string inputcode =
256-
@"Sub Foo()
278+
@"Sub Foo()
257279
Dim d
258280
If True Then
259281
d = True ' test
Lines changed: 136 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,136 @@
1+
using System.Linq;
2+
using System.Threading;
3+
using Microsoft.VisualStudio.TestTools.UnitTesting;
4+
using Rubberduck.Inspections.Concrete;
5+
using Rubberduck.Inspections.QuickFixes;
6+
using RubberduckTests.Mocks;
7+
using RubberduckTests.Inspections;
8+
9+
namespace RubberduckTests.QuickFixes
10+
{
11+
[TestClass]
12+
public class ReplaceIfElseWithConditionalStatementQuickFixTests
13+
{
14+
[TestMethod]
15+
[TestCategory("QuickFixes")]
16+
public void Simple()
17+
{
18+
const string inputCode =
19+
@"Sub Foo()
20+
Dim d As Boolean
21+
If True Then
22+
d = True
23+
Else
24+
d = False
25+
EndIf
26+
End Sub";
27+
28+
const string expectedCode =
29+
@"Sub Foo()
30+
Dim d As Boolean
31+
d = True
32+
End Sub";
33+
34+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component);
35+
var state = MockParser.CreateAndParse(vbe.Object);
36+
37+
var inspection = new BooleanAssignedInIfElseInspection(state);
38+
var inspector = InspectionsHelper.GetInspector(inspection);
39+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
40+
41+
new ReplaceIfElseWithConditionalStatementQuickFix(state).Fix(inspectionResults.First());
42+
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
43+
}
44+
45+
[TestMethod]
46+
[TestCategory("QuickFixes")]
47+
public void ComplexCondition()
48+
{
49+
const string inputCode =
50+
@"Sub Foo()
51+
Dim d As Boolean
52+
If True Or False And False Xor True Then
53+
d = True
54+
Else
55+
d = False
56+
EndIf
57+
End Sub";
58+
59+
const string expectedCode =
60+
@"Sub Foo()
61+
Dim d As Boolean
62+
d = True Or False And False Xor True
63+
End Sub";
64+
65+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component);
66+
var state = MockParser.CreateAndParse(vbe.Object);
67+
68+
var inspection = new BooleanAssignedInIfElseInspection(state);
69+
var inspector = InspectionsHelper.GetInspector(inspection);
70+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
71+
72+
new ReplaceIfElseWithConditionalStatementQuickFix(state).Fix(inspectionResults.First());
73+
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
74+
}
75+
76+
[TestMethod]
77+
[TestCategory("QuickFixes")]
78+
public void InvertedCondition()
79+
{
80+
const string inputCode =
81+
@"Sub Foo()
82+
Dim d As Boolean
83+
If True Then
84+
d = False
85+
Else
86+
d = True
87+
EndIf
88+
End Sub";
89+
90+
const string expectedCode =
91+
@"Sub Foo()
92+
Dim d As Boolean
93+
d = Not (True)
94+
End Sub";
95+
96+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component);
97+
var state = MockParser.CreateAndParse(vbe.Object);
98+
99+
var inspection = new BooleanAssignedInIfElseInspection(state);
100+
var inspector = InspectionsHelper.GetInspector(inspection);
101+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
102+
103+
new ReplaceIfElseWithConditionalStatementQuickFix(state).Fix(inspectionResults.First());
104+
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
105+
}
106+
107+
[TestMethod]
108+
[TestCategory("QuickFixes")]
109+
public void QualifiedName()
110+
{
111+
const string inputCode =
112+
@"Sub Foo()
113+
If True Then
114+
Fizz.Buzz = True
115+
Else
116+
Fizz.Buzz = False
117+
EndIf
118+
End Sub";
119+
120+
const string expectedCode =
121+
@"Sub Foo()
122+
Fizz.Buzz = True
123+
End Sub";
124+
125+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component);
126+
var state = MockParser.CreateAndParse(vbe.Object);
127+
128+
var inspection = new BooleanAssignedInIfElseInspection(state);
129+
var inspector = InspectionsHelper.GetInspector(inspection);
130+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
131+
132+
new ReplaceIfElseWithConditionalStatementQuickFix(state).Fix(inspectionResults.First());
133+
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
134+
}
135+
}
136+
}

RubberduckTests/RubberduckTests.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -124,6 +124,7 @@
124124
<Compile Include="QuickFixes\AssignedByValParameterMakeLocalCopyQuickFixTests.cs" />
125125
<Compile Include="QuickFixes\ChangeProcedureToFunctionQuickFixTests.cs" />
126126
<Compile Include="QuickFixes\DeclareAsExplicitVariantQuickFixTests.cs" />
127+
<Compile Include="QuickFixes\ReplaceIfElseWithConditionalStatementQuickFixTests.cs" />
127128
<Compile Include="QuickFixes\PassParameterByReferenceQuickFixTests.cs" />
128129
<Compile Include="QuickFixes\QuickFixProviderTests.cs" />
129130
<Compile Include="QuickFixes\RemoveUnassignedIdentifierQuickFixTests.cs" />

0 commit comments

Comments
 (0)