Skip to content

Commit b1384d3

Browse files
authored
Merge pull request #3661 from rkapka/rkapka-master
UnhandledOnErrorResumeNext inspection
2 parents aed28aa + fe17236 commit b1384d3

20 files changed

+849
-56
lines changed

RetailCoder.VBE/UI/Inspections/AggregateInspectionResult.cs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
using System;
2-
using System.Collections.Generic;
32
using Antlr4.Runtime;
43
using Rubberduck.Parsing.Inspections.Abstract;
54
using Rubberduck.Parsing.Inspections.Resources;
@@ -29,16 +28,16 @@ public AggregateInspectionResult(IInspectionResult firstResult, int count)
2928

3029
public ParserRuleContext Context => _result.Context;
3130

32-
public IDictionary<string, string> Properties => throw new NotImplementedException();
31+
public dynamic Properties => throw new NotImplementedException();
3332

3433
public int CompareTo(IInspectionResult other)
3534
{
3635
if (other == this)
3736
{
3837
return 0;
3938
}
40-
var aggregated = other as AggregateInspectionResult;
41-
if (aggregated == null)
39+
40+
if (!(other is AggregateInspectionResult aggregated))
4241
{
4342
return -1;
4443
}

Rubberduck.Inspections/Abstract/InspectionResultBase.cs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
1-
using System.Collections.Generic;
2-
using System.IO;
1+
using System.IO;
32
using Antlr4.Runtime;
43
using Rubberduck.Common;
4+
using Rubberduck.Parsing.Inspections;
55
using Rubberduck.Parsing.Inspections.Abstract;
66
using Rubberduck.Parsing.Inspections.Resources;
77
using Rubberduck.Parsing.Symbols;
@@ -20,7 +20,7 @@ protected InspectionResultBase(IInspection inspection,
2020
Declaration target,
2121
QualifiedSelection qualifiedSelection,
2222
QualifiedMemberName? qualifiedMemberName,
23-
Dictionary<string, string> properties)
23+
dynamic properties)
2424
{
2525
Inspection = inspection;
2626
Description = description?.Capitalize();
@@ -29,7 +29,7 @@ protected InspectionResultBase(IInspection inspection,
2929
Target = target;
3030
QualifiedSelection = qualifiedSelection;
3131
QualifiedMemberName = qualifiedMemberName;
32-
Properties = properties ?? new Dictionary<string, string>();
32+
Properties = properties ?? new PropertyBag();
3333
}
3434

3535
public IInspection Inspection { get; }
@@ -38,7 +38,7 @@ protected InspectionResultBase(IInspection inspection,
3838
public QualifiedMemberName? QualifiedMemberName { get; }
3939
public ParserRuleContext Context { get; }
4040
public Declaration Target { get; }
41-
public IDictionary<string, string> Properties { get; }
41+
public dynamic Properties { get; }
4242

4343
/// <summary>
4444
/// Gets the information needed to select the target instruction in the VBE.

Rubberduck.Inspections/Concrete/FunctionReturnValueNotUsedInspection.cs

Lines changed: 25 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
using Rubberduck.Inspections.Abstract;
66
using Rubberduck.Inspections.Results;
77
using Rubberduck.Parsing.Grammar;
8+
using Rubberduck.Parsing.Inspections;
89
using Rubberduck.Parsing.Inspections.Abstract;
910
using Rubberduck.Parsing.Inspections.Resources;
1011
using Rubberduck.Parsing.Symbols;
@@ -40,21 +41,19 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4041
private IEnumerable<IInspectionResult> GetInterfaceMemberIssues(IEnumerable<Declaration> interfaceMembers)
4142
{
4243
return from interfaceMember in interfaceMembers
43-
let implementationMembers =
44-
UserDeclarations.FindInterfaceImplementationMembers(interfaceMember.IdentifierName).ToList()
45-
where interfaceMember.DeclarationType == DeclarationType.Function &&
46-
!IsReturnValueUsed(interfaceMember) &&
47-
implementationMembers.All(member => !IsReturnValueUsed(member))
48-
let implementationMemberIssues =
49-
implementationMembers.Select(
50-
implementationMember =>
51-
Tuple.Create(implementationMember.Context,
52-
new QualifiedSelection(implementationMember.QualifiedName.QualifiedModuleName,
53-
implementationMember.Selection), implementationMember))
54-
select
55-
new DeclarationInspectionResult(this,
56-
string.Format(InspectionsUI.FunctionReturnValueNotUsedInspectionResultFormat, interfaceMember.IdentifierName),
57-
interfaceMember, properties: new Dictionary<string, string> { { "DisableFixes", nameof(QuickFixes.ConvertToProcedureQuickFix) } });
44+
let implementationMembers =
45+
UserDeclarations.FindInterfaceImplementationMembers(interfaceMember.IdentifierName).ToList()
46+
where interfaceMember.DeclarationType == DeclarationType.Function &&
47+
!IsReturnValueUsed(interfaceMember) &&
48+
implementationMembers.All(member => !IsReturnValueUsed(member))
49+
let implementationMemberIssues =
50+
implementationMembers.Select(
51+
implementationMember =>
52+
Tuple.Create(implementationMember.Context,
53+
new QualifiedSelection(implementationMember.QualifiedName.QualifiedModuleName,
54+
implementationMember.Selection), implementationMember))
55+
select CreateInspectionResult(this, interfaceMember);
56+
5857
}
5958

6059
private IEnumerable<IInspectionResult> GetNonInterfaceIssues(IEnumerable<Declaration> nonInterfaceFunctions)
@@ -149,5 +148,16 @@ private bool IsSet(IdentifierReference usage)
149148

150149
return setStmt != null && setStmt == usage.Context;
151150
}
151+
152+
private DeclarationInspectionResult CreateInspectionResult(IInspection inspection, Declaration interfaceMember)
153+
{
154+
dynamic properties = new PropertyBag();
155+
properties.DisableFixes = nameof(QuickFixes.ConvertToProcedureQuickFix);
156+
157+
return new DeclarationInspectionResult(inspection,
158+
string.Format(InspectionsUI.FunctionReturnValueNotUsedInspectionResultFormat,
159+
interfaceMember.IdentifierName),
160+
interfaceMember, properties: properties);
161+
}
152162
}
153163
}
Lines changed: 124 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,124 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Antlr4.Runtime;
4+
using Rubberduck.Inspections.Abstract;
5+
using Rubberduck.Inspections.Results;
6+
using Rubberduck.Parsing;
7+
using Rubberduck.Parsing.Grammar;
8+
using Rubberduck.Parsing.Inspections;
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 class UnhandledOnErrorResumeNextInspection : ParseTreeInspectionBase
17+
{
18+
private readonly Dictionary<QualifiedContext<ParserRuleContext>, string> _errorHandlerLabelsMap =
19+
new Dictionary<QualifiedContext<ParserRuleContext>, string>();
20+
private readonly Dictionary<QualifiedContext<ParserRuleContext>, VBAParser.ModuleBodyElementContext> _bodyElementContextsMap =
21+
new Dictionary<QualifiedContext<ParserRuleContext>, VBAParser.ModuleBodyElementContext>();
22+
23+
public UnhandledOnErrorResumeNextInspection(RubberduckParserState state,
24+
CodeInspectionSeverity defaultSeverity = CodeInspectionSeverity.Warning) : base(state, defaultSeverity)
25+
{
26+
Listener = new OnErrorStatementListener(_errorHandlerLabelsMap, _bodyElementContextsMap);
27+
}
28+
29+
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
30+
31+
public override IInspectionListener Listener { get; }
32+
33+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
34+
{
35+
return Listener.Contexts
36+
.Where(result => !IsIgnoringInspectionResultFor(result.ModuleName, result.Context.Start.Line))
37+
.Select(result =>
38+
{
39+
dynamic properties = new PropertyBag();
40+
properties.Label = _errorHandlerLabelsMap[result];
41+
properties.BodyElement = _bodyElementContextsMap[result];
42+
43+
return new QualifiedContextInspectionResult(this, InspectionsUI.UnhandledOnErrorResumeNextInspectionResultFormat, result, properties);
44+
});
45+
}
46+
}
47+
48+
public class OnErrorStatementListener : VBAParserBaseListener, IInspectionListener
49+
{
50+
private readonly List<QualifiedContext<ParserRuleContext>> _contexts = new List<QualifiedContext<ParserRuleContext>>();
51+
private readonly List<QualifiedContext<ParserRuleContext>> _unhandledContexts = new List<QualifiedContext<ParserRuleContext>>();
52+
private readonly List<string> _errorHandlerLabels = new List<string>();
53+
private readonly Dictionary<QualifiedContext<ParserRuleContext>, string> _errorHandlerLabelsMap;
54+
private readonly Dictionary<QualifiedContext<ParserRuleContext>, VBAParser.ModuleBodyElementContext> _bodyElementContextsMap;
55+
56+
private const string LabelPrefix = "ErrorHandler";
57+
58+
public OnErrorStatementListener(Dictionary<QualifiedContext<ParserRuleContext>, string> errorHandlerLabelsMap,
59+
Dictionary<QualifiedContext<ParserRuleContext>, VBAParser.ModuleBodyElementContext> bodyElementContextsMap)
60+
{
61+
_errorHandlerLabelsMap = errorHandlerLabelsMap;
62+
_bodyElementContextsMap = bodyElementContextsMap;
63+
}
64+
65+
public IReadOnlyList<QualifiedContext<ParserRuleContext>> Contexts => _contexts;
66+
67+
public void ClearContexts()
68+
{
69+
_contexts.Clear();
70+
}
71+
72+
public QualifiedModuleName CurrentModuleName { get; set; }
73+
74+
public override void ExitModuleBodyElement(VBAParser.ModuleBodyElementContext context)
75+
{
76+
if (_unhandledContexts.Any())
77+
{
78+
var labelIndex = -1;
79+
80+
foreach (var errorContext in _unhandledContexts)
81+
{
82+
_bodyElementContextsMap.Add(errorContext, context);
83+
84+
labelIndex++;
85+
var labelSuffix = labelIndex == 0 ? "" : labelIndex.ToString();
86+
87+
while (_errorHandlerLabels.Contains($"{LabelPrefix.ToLower()}{labelSuffix}"))
88+
{
89+
labelIndex++;
90+
labelSuffix = labelIndex == 0 ? "" : labelIndex.ToString();
91+
}
92+
93+
_errorHandlerLabelsMap.Add(errorContext, $"{LabelPrefix}{labelSuffix}");
94+
}
95+
96+
_contexts.AddRange(_unhandledContexts);
97+
98+
_unhandledContexts.Clear();
99+
_errorHandlerLabels.Clear();
100+
}
101+
}
102+
103+
public override void ExitOnErrorStmt(VBAParser.OnErrorStmtContext context)
104+
{
105+
if (context.RESUME() != null)
106+
{
107+
_unhandledContexts.Add(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context));
108+
}
109+
else if (context.GOTO() != null)
110+
{
111+
_unhandledContexts.Clear();
112+
}
113+
}
114+
115+
public override void ExitIdentifierStatementLabel(VBAParser.IdentifierStatementLabelContext context)
116+
{
117+
var labelText = context.unrestrictedIdentifier().identifier().untypedIdentifier().identifierValue().IDENTIFIER().GetText();
118+
if (labelText.ToLower().StartsWith(LabelPrefix.ToLower()))
119+
{
120+
_errorHandlerLabels.Add(labelText.ToLower());
121+
}
122+
}
123+
}
124+
}

Rubberduck.Inspections/Concrete/UseMeaningfulNameInspection.cs

Lines changed: 20 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Rubberduck.Common;
55
using Rubberduck.Inspections.Abstract;
66
using Rubberduck.Inspections.Results;
7+
using Rubberduck.Parsing.Inspections;
78
using Rubberduck.Parsing.Inspections.Abstract;
89
using Rubberduck.Parsing.Inspections.Resources;
910
using Rubberduck.Parsing.Symbols;
@@ -51,15 +52,26 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5152
!whitelistedNames.Contains(declaration.IdentifierName) &&
5253
!VariableNameValidator.IsMeaningfulName(declaration.IdentifierName));
5354

54-
return (from issue in issues
55-
let props = issue.DeclarationType.HasFlag(DeclarationType.Module) ||
56-
issue.DeclarationType.HasFlag(DeclarationType.Project)
57-
? new Dictionary<string, string> {{"DisableFixes", "IgnoreOnceQuickFix"}} : null
58-
select new DeclarationInspectionResult(this,
59-
string.Format(InspectionsUI.IdentifierNameInspectionResultFormat,
60-
RubberduckUI.ResourceManager.GetString("DeclarationType_" + issue.DeclarationType,
61-
CultureInfo.CurrentUICulture), issue.IdentifierName), issue, properties: props))
55+
return (from issue in issues select CreateInspectionResult(this, issue))
6256
.ToList();
6357
}
58+
59+
private static DeclarationInspectionResult CreateInspectionResult(IInspection inspection, Declaration issue)
60+
{
61+
dynamic properties = null;
62+
63+
if (issue.DeclarationType.HasFlag(DeclarationType.Module) ||
64+
issue.DeclarationType.HasFlag(DeclarationType.Project))
65+
{
66+
properties = new PropertyBag();
67+
properties.DisableFixes = "IgnoreOnceQuickFix";
68+
}
69+
70+
return new DeclarationInspectionResult(inspection,
71+
string.Format(InspectionsUI.IdentifierNameInspectionResultFormat,
72+
RubberduckUI.ResourceManager.GetString("DeclarationType_" + issue.DeclarationType,
73+
CultureInfo.CurrentUICulture), issue.IdentifierName),
74+
issue, properties: properties);
75+
}
6476
}
6577
}

Rubberduck.Inspections/QuickFixProvider.cs

Lines changed: 18 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
using System.Collections.Generic;
33
using System.Diagnostics;
44
using System.Linq;
5+
using Microsoft.CSharp.RuntimeBinder;
56
using Rubberduck.Parsing.Inspections.Abstract;
67
using Rubberduck.Parsing.VBA;
78
using Rubberduck.VBEditor;
@@ -40,15 +41,25 @@ public IEnumerable<IQuickFix> QuickFixes(IInspectionResult result)
4041
}
4142

4243
return _quickFixes[result.Inspection.GetType()].Where(fix =>
43-
{
44-
if (!result.Properties.TryGetValue("DisableFixes", out var value))
4544
{
46-
return true;
47-
}
45+
string value;
46+
try
47+
{
48+
value = result.Properties.DisableFixes;
49+
}
50+
catch (RuntimeBinderException)
51+
{
52+
return true;
53+
}
54+
55+
if (value == null)
56+
{
57+
return true;
58+
}
4859

49-
return !value.Split(',').Contains(fix.GetType().Name);
50-
})
51-
.OrderBy(fix => fix.SupportedInspections.Count); // most specific fixes first; keeps "ignore once" last
60+
return !value.Split(',').Contains(fix.GetType().Name);
61+
})
62+
.OrderBy(fix => fix.SupportedInspections.Count); // most specific fixes first; keeps "ignore once" last
5263
}
5364

5465
private bool CanFix(IQuickFix fix, IInspectionResult result)

0 commit comments

Comments
 (0)