Skip to content

Commit 747eaf6

Browse files
authored
Merge pull request #3428 from Hosch250/twoKeyCommands
Inspection for obsolete Error statement and quickfix to replace with Err.Raise calls.
2 parents 1353d33 + 9e6af52 commit 747eaf6

10 files changed

+385
-2
lines changed
Lines changed: 53 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,53 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using Antlr4.Runtime;
5+
using Rubberduck.Inspections.Abstract;
6+
using Rubberduck.Inspections.Results;
7+
using Rubberduck.Parsing;
8+
using Rubberduck.Parsing.Grammar;
9+
using Rubberduck.Parsing.Inspections.Abstract;
10+
using Rubberduck.Parsing.Inspections.Resources;
11+
using Rubberduck.Parsing.VBA;
12+
using Rubberduck.VBEditor;
13+
14+
namespace Rubberduck.Inspections.Concrete
15+
{
16+
public sealed class ObsoleteErrorSyntaxInspection : ParseTreeInspectionBase
17+
{
18+
public ObsoleteErrorSyntaxInspection(RubberduckParserState state)
19+
: base(state, CodeInspectionSeverity.Suggestion)
20+
{
21+
Listener = new ObsoleteErrorSyntaxListener();
22+
}
23+
24+
public override Type Type => typeof(ObsoleteErrorSyntaxInspection);
25+
26+
public override CodeInspectionType InspectionType => CodeInspectionType.LanguageOpportunities;
27+
public override IInspectionListener Listener { get; }
28+
29+
public override IEnumerable<IInspectionResult> GetInspectionResults()
30+
{
31+
return Listener.Contexts.Where(context => !IsIgnoringInspectionResultFor(context.ModuleName, context.Context.Start.Line))
32+
.Select(context => new QualifiedContextInspectionResult(this, InspectionsUI.ObsoleteErrorSyntaxInspectionResultFormat, context));
33+
}
34+
35+
public class ObsoleteErrorSyntaxListener : VBAParserBaseListener, IInspectionListener
36+
{
37+
private readonly List<QualifiedContext<ParserRuleContext>> _contexts = new List<QualifiedContext<ParserRuleContext>>();
38+
public IReadOnlyList<QualifiedContext<ParserRuleContext>> Contexts => _contexts;
39+
40+
public QualifiedModuleName CurrentModuleName { get; set; }
41+
42+
public void ClearContexts()
43+
{
44+
_contexts.Clear();
45+
}
46+
47+
public override void ExitErrorStmt(VBAParser.ErrorStmtContext context)
48+
{
49+
_contexts.Add(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context));
50+
}
51+
}
52+
}
53+
}
Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,37 @@
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.VBA;
7+
8+
namespace Rubberduck.Inspections.QuickFixes
9+
{
10+
public sealed class ReplaceObsoleteErrorStatementQuickFix : QuickFixBase
11+
{
12+
private readonly RubberduckParserState _state;
13+
14+
public ReplaceObsoleteErrorStatementQuickFix(RubberduckParserState state)
15+
: base(typeof(ObsoleteErrorSyntaxInspection))
16+
{
17+
_state = state;
18+
}
19+
20+
public override void Fix(IInspectionResult result)
21+
{
22+
var rewriter = _state.GetRewriter(result.QualifiedSelection.QualifiedName);
23+
var context = (VBAParser.ErrorStmtContext) result.Context;
24+
25+
rewriter.Replace(context.ERROR(), "Err.Raise");
26+
}
27+
28+
public override string Description(IInspectionResult result)
29+
{
30+
return InspectionsUI.ReplaceObsoleteErrorStatementQuickFix;
31+
}
32+
33+
public override bool CanFixInProcedure => true;
34+
public override bool CanFixInModule => true;
35+
public override bool CanFixInProject => true;
36+
}
37+
}

Rubberduck.Inspections/Rubberduck.Inspections.csproj

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -68,6 +68,7 @@
6868
<Compile Include="Concrete\EmptyForEachBlockInspection.cs" />
6969
<Compile Include="Concrete\EmptyForLoopBlockInspection.cs" />
7070
<Compile Include="Concrete\EmptyWhileWendBlockInspection.cs" />
71+
<Compile Include="Concrete\ObsoleteErrorSyntaxInspection.cs" />
7172
<Compile Include="Concrete\StopKeywordInspection.cs" />
7273
<Compile Include="Concrete\LineLabelNotUsedInspection.cs" />
7374
<Compile Include="Concrete\IntegerDataTypeInspection.cs" />
@@ -122,6 +123,7 @@
122123
<Compile Include="QuickFixes\ChangeIntegerToLongQuickFix.cs" />
123124
<Compile Include="Abstract\QuickFixBase.cs" />
124125
<Compile Include="QuickFixes\RemoveStopKeywordQuickFix.cs" />
126+
<Compile Include="QuickFixes\ReplaceObsoleteErrorStatementQuickFix.cs" />
125127
<Compile Include="QuickFixes\SpecifyExplicitByRefModifierQuickFix.cs" />
126128
<Compile Include="QuickFixes\ChangeProcedureToFunctionQuickFix.cs" />
127129
<Compile Include="QuickFixes\ConvertToProcedureQuickFix.cs" />

Rubberduck.Parsing/Inspections/Resources/InspectionsUI.resx

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -857,4 +857,13 @@ If the parameter can be null, ignore this inspection result; passing a null valu
857857
<data name="ShadowedDeclarationInspectionResultFormat" xml:space="preserve">
858858
<value>{0} '{1}' hides {2} '{3}'</value>
859859
</data>
860+
<data name="ObsoleteErrorSyntaxInspectionMeta" xml:space="preserve">
861+
<value>The 'Error' statement only exists in the language to support legacy code that required it; prefer using 'Err.Raise' instead.</value>
862+
</data>
863+
<data name="ObsoleteErrorSyntaxInspectionResultFormat" xml:space="preserve">
864+
<value>Error throw uses obsolete 'Error' statement</value>
865+
</data>
866+
<data name="ReplaceObsoleteErrorStatementQuickFix" xml:space="preserve">
867+
<value>Replace 'Error' with 'Err.Raise'</value>
868+
</data>
860869
</root>

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

Lines changed: 27 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.
Lines changed: 106 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,106 @@
1+
using System.Linq;
2+
using System.Threading;
3+
using Microsoft.VisualStudio.TestTools.UnitTesting;
4+
using Rubberduck.Inspections.Concrete;
5+
using Rubberduck.Parsing.Inspections.Resources;
6+
using RubberduckTests.Mocks;
7+
8+
namespace RubberduckTests.Inspections
9+
{
10+
[TestClass]
11+
public class ObsoleteErrorSyntaxInspectionTests
12+
{
13+
[TestMethod]
14+
[TestCategory("Inspections")]
15+
public void ObsoleteErrorSyntax_ReturnsResult()
16+
{
17+
const string inputCode =
18+
@"Sub Foo()
19+
Error 91
20+
End Sub";
21+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
22+
var state = MockParser.CreateAndParse(vbe.Object);
23+
24+
var inspection = new ObsoleteErrorSyntaxInspection(state);
25+
var inspector = InspectionsHelper.GetInspector(inspection);
26+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
27+
28+
Assert.AreEqual(1, inspectionResults.Count());
29+
}
30+
31+
[TestMethod]
32+
[TestCategory("Inspections")]
33+
public void ObsoleteErrorSyntax_DoesNotReturnResult_ErrorInStringLiteral()
34+
{
35+
const string inputCode =
36+
@"Sub Foo()
37+
Dim bar As String
38+
bar = ""Error 91"" ' test
39+
End Sub";
40+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
41+
var state = MockParser.CreateAndParse(vbe.Object);
42+
43+
var inspection = new ObsoleteErrorSyntaxInspection(state);
44+
var inspector = InspectionsHelper.GetInspector(inspection);
45+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
46+
47+
Assert.AreEqual(0, inspectionResults.Count());
48+
}
49+
50+
[TestMethod]
51+
[TestCategory("Inspections")]
52+
public void ObsoleteErrorSyntax_ReturnsMultipleResults()
53+
{
54+
const string inputCode =
55+
@"Sub Foo()
56+
Error 91
57+
Error 91
58+
End Sub";
59+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
60+
var state = MockParser.CreateAndParse(vbe.Object);
61+
62+
var inspection = new ObsoleteErrorSyntaxInspection(state);
63+
var inspector = InspectionsHelper.GetInspector(inspection);
64+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
65+
66+
Assert.AreEqual(2, inspectionResults.Count());
67+
}
68+
69+
[TestMethod]
70+
[TestCategory("Inspections")]
71+
public void ObsoleteErrorSyntax_Ignored_DoesNotReturnResult()
72+
{
73+
const string inputCode =
74+
@"Sub Foo()
75+
'@Ignore ObsoleteErrorSyntax
76+
Error 91
77+
End Sub";
78+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
79+
var state = MockParser.CreateAndParse(vbe.Object);
80+
81+
var inspection = new ObsoleteErrorSyntaxInspection(state);
82+
var inspector = InspectionsHelper.GetInspector(inspection);
83+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
84+
85+
Assert.IsFalse(inspectionResults.Any());
86+
}
87+
88+
[TestMethod]
89+
[TestCategory("Inspections")]
90+
public void InspectionType()
91+
{
92+
var inspection = new ObsoleteErrorSyntaxInspection(null);
93+
Assert.AreEqual(CodeInspectionType.LanguageOpportunities, inspection.InspectionType);
94+
}
95+
96+
[TestMethod]
97+
[TestCategory("Inspections")]
98+
public void InspectionName()
99+
{
100+
const string inspectionName = "ObsoleteErrorSyntaxInspection";
101+
var inspection = new ObsoleteErrorSyntaxInspection(null);
102+
103+
Assert.AreEqual(inspectionName, inspection.Name);
104+
}
105+
}
106+
}

RubberduckTests/QuickFixes/IgnoreOnceQuickFixTests.cs

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -633,6 +633,31 @@ public void ObsoleteCommentSyntax_IgnoreQuickFixWorks()
633633
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
634634
}
635635

636+
[TestMethod]
637+
[TestCategory("QuickFixes")]
638+
public void ObsoleteErrorSyntax_IgnoreQuickFixWorks()
639+
{
640+
const string inputCode =
641+
@"Sub Foo()
642+
Error 91
643+
End Sub";
644+
645+
const string expectedCode =
646+
@"Sub Foo()
647+
'@Ignore ObsoleteErrorSyntax
648+
Error 91
649+
End Sub";
650+
651+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component);
652+
var state = MockParser.CreateAndParse(vbe.Object);
653+
654+
var inspection = new ObsoleteErrorSyntaxInspection(state);
655+
var inspector = InspectionsHelper.GetInspector(inspection);
656+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
657+
658+
new IgnoreOnceQuickFix(state, new[] { inspection }).Fix(inspectionResults.First());
659+
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
660+
}
636661

637662
[TestMethod]
638663
[TestCategory("QuickFixes")]

RubberduckTests/QuickFixes/ReplaceOboleteCommentMarkerQuickFixTests.cs renamed to RubberduckTests/QuickFixes/ReplaceObsoleteCommentMarkerQuickFixTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@
99
namespace RubberduckTests.QuickFixes
1010
{
1111
[TestClass]
12-
public class ReplaceOboleteCommentMarkerQuickFixTests
12+
public class ReplaceObsoleteCommentMarkerQuickFixTests
1313
{
1414
[TestMethod]
1515
[TestCategory("QuickFixes")]

0 commit comments

Comments
 (0)