Skip to content

Commit c58f68d

Browse files
authored
Merge pull request #2555 from comintern/next
Convert ObsoleteCommentSyntaxInspection to listener.
2 parents 8dcf4f7 + eb029c4 commit c58f68d

File tree

9 files changed

+285
-114
lines changed

9 files changed

+285
-114
lines changed

RetailCoder.VBE/Inspections/Concrete/Inspector.cs

Lines changed: 26 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -119,25 +119,46 @@ before moving them into the ParseTreeResults after qualifying them
119119
*/
120120
var obsoleteCallStatementListener = IsDisabled<ObsoleteCallStatementInspection>(settings) ? null : new ObsoleteCallStatementInspection.ObsoleteCallStatementListener();
121121
var obsoleteLetStatementListener = IsDisabled<ObsoleteLetStatementInspection>(settings) ? null : new ObsoleteLetStatementInspection.ObsoleteLetStatementListener();
122+
var obsoleteCommentSyntaxListener = IsDisabled<ObsoleteCommentSyntaxInspection>(settings) ? null : new ObsoleteCommentSyntaxInspection.ObsoleteCommentSyntaxListener();
122123
var emptyStringLiteralListener = IsDisabled<EmptyStringLiteralInspection>(settings) ? null : new EmptyStringLiteralInspection.EmptyStringLiteralListener();
123124
var argListWithOneByRefParamListener = IsDisabled<ProcedureCanBeWrittenAsFunctionInspection>(settings) ? null : new ProcedureCanBeWrittenAsFunctionInspection.SingleByRefParamArgListListener();
124125
var invalidAnnotationListener = IsDisabled<MissingAnnotationArgumentInspection>(settings) ? null : new MissingAnnotationArgumentInspection.InvalidAnnotationStatementListener();
125126

126127
var combinedListener = new CombinedParseTreeListener(new IParseTreeListener[]{
127128
obsoleteCallStatementListener,
128129
obsoleteLetStatementListener,
130+
obsoleteCommentSyntaxListener,
129131
emptyStringLiteralListener,
130132
argListWithOneByRefParamListener,
131133
invalidAnnotationListener
132134
});
133135

134136
ParseTreeWalker.Default.Walk(combinedListener, componentTreePair.Value);
135137

136-
result.AddRange(argListWithOneByRefParamListener.Contexts.Select(context => new QualifiedContext<VBAParser.ArgListContext>(componentTreePair.Key, context)));
137-
result.AddRange(emptyStringLiteralListener.Contexts.Select(context => new QualifiedContext<VBAParser.LiteralExpressionContext>(componentTreePair.Key, context)));
138-
result.AddRange(obsoleteLetStatementListener.Contexts.Select(context => new QualifiedContext<VBAParser.LetStmtContext>(componentTreePair.Key, context)));
139-
result.AddRange(obsoleteCallStatementListener.Contexts.Select(context => new QualifiedContext<VBAParser.CallStmtContext>(componentTreePair.Key, context)));
140-
result.AddRange(invalidAnnotationListener.Contexts.Select(context => new QualifiedContext<VBAParser.AnnotationContext>(componentTreePair.Key, context)));
138+
if (argListWithOneByRefParamListener != null)
139+
{
140+
result.AddRange(argListWithOneByRefParamListener.Contexts.Select(context => new QualifiedContext<VBAParser.ArgListContext>(componentTreePair.Key, context)));
141+
}
142+
if (emptyStringLiteralListener != null)
143+
{
144+
result.AddRange(emptyStringLiteralListener.Contexts.Select(context => new QualifiedContext<VBAParser.LiteralExpressionContext>(componentTreePair.Key, context)));
145+
}
146+
if (obsoleteLetStatementListener != null)
147+
{
148+
result.AddRange(obsoleteLetStatementListener.Contexts.Select(context => new QualifiedContext<VBAParser.LetStmtContext>(componentTreePair.Key, context)));
149+
}
150+
if (obsoleteCommentSyntaxListener != null)
151+
{
152+
result.AddRange(obsoleteCommentSyntaxListener.Contexts.Select(context => new QualifiedContext<VBAParser.RemCommentContext>(componentTreePair.Key, context)));
153+
}
154+
if (obsoleteCallStatementListener != null)
155+
{
156+
result.AddRange(obsoleteCallStatementListener.Contexts.Select(context => new QualifiedContext<VBAParser.CallStmtContext>(componentTreePair.Key, context)));
157+
}
158+
if (invalidAnnotationListener != null)
159+
{
160+
result.AddRange(invalidAnnotationListener.Contexts.Select(context => new QualifiedContext<VBAParser.AnnotationContext>(componentTreePair.Key, context)));
161+
}
141162
}
142163
return result;
143164
}
Lines changed: 36 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,32 +1,56 @@
11
using System.Collections.Generic;
22
using System.Linq;
3+
using Antlr4.Runtime;
34
using Rubberduck.Inspections.Abstract;
45
using Rubberduck.Inspections.Resources;
56
using Rubberduck.Inspections.Results;
7+
using Rubberduck.Parsing;
68
using Rubberduck.Parsing.Grammar;
79
using Rubberduck.Parsing.VBA;
810

911
namespace Rubberduck.Inspections
1012
{
11-
public sealed class ObsoleteCommentSyntaxInspection : InspectionBase
13+
public sealed class ObsoleteCommentSyntaxInspection : InspectionBase, IParseTreeInspection<VBAParser.RemCommentContext>
1214
{
13-
/// <summary>
14-
/// Parameterless constructor required for discovery of implemented code inspections.
15-
/// </summary>
16-
public ObsoleteCommentSyntaxInspection(RubberduckParserState state)
17-
: base(state, CodeInspectionSeverity.Suggestion)
18-
{
19-
}
15+
private IEnumerable<QualifiedContext> _results;
16+
17+
public ObsoleteCommentSyntaxInspection(RubberduckParserState state) : base(state, CodeInspectionSeverity.Suggestion) { }
2018

2119
public override string Meta { get { return InspectionsUI.ObsoleteCommentSyntaxInspectionMeta; } }
2220
public override string Description { get { return InspectionsUI.ObsoleteCommentSyntaxInspectionName; } }
23-
public override CodeInspectionType InspectionType { get {return CodeInspectionType.LanguageOpportunities; } }
21+
public override CodeInspectionType InspectionType { get { return CodeInspectionType.LanguageOpportunities; } }
2422

2523
public override IEnumerable<InspectionResultBase> GetInspectionResults()
2624
{
27-
return State.AllComments.Where(comment => comment.Marker == Tokens.Rem &&
28-
!IsInspectionDisabled(comment.QualifiedSelection.QualifiedName.Component, comment.QualifiedSelection.Selection.StartLine))
29-
.Select(comment => new ObsoleteCommentSyntaxInspectionResult(this, comment));
25+
if (ParseTreeResults == null)
26+
{
27+
return new InspectionResultBase[] { };
28+
}
29+
return ParseTreeResults.Where(context => !IsInspectionDisabled(context.ModuleName.Component, context.Context.Start.Line))
30+
.Select(context => new ObsoleteCommentSyntaxInspectionResult(this, new QualifiedContext<ParserRuleContext>(context.ModuleName, context.Context)));
31+
}
32+
33+
public void SetResults(IEnumerable<QualifiedContext> results)
34+
{
35+
_results = results;
36+
}
37+
38+
public IEnumerable<QualifiedContext<VBAParser.RemCommentContext>> ParseTreeResults { get { return _results.OfType<QualifiedContext<VBAParser.RemCommentContext>>(); } }
39+
40+
41+
public class ObsoleteCommentSyntaxListener : VBAParserBaseListener
42+
{
43+
private readonly IList<VBAParser.RemCommentContext> _contexts = new List<VBAParser.RemCommentContext>();
44+
45+
public IEnumerable<VBAParser.RemCommentContext> Contexts
46+
{
47+
get { return _contexts; }
48+
}
49+
50+
public override void ExitRemComment(VBAParser.RemCommentContext context)
51+
{
52+
_contexts.Add(context);
53+
}
3054
}
3155
}
3256
}

RetailCoder.VBE/Inspections/ObsoleteLetStatementInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -35,8 +35,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3535
{
3636
return new InspectionResultBase[] { };
3737
}
38-
return ParseTreeResults.OfType<QualifiedContext<VBAParser.LetStmtContext>>()
39-
.Where(context => !IsInspectionDisabled(context.ModuleName.Component, context.Context.Start.Line))
38+
return ParseTreeResults.Where(context => !IsInspectionDisabled(context.ModuleName.Component, context.Context.Start.Line))
4039
.Select(context => new ObsoleteLetStatementUsageInspectionResult(this, new QualifiedContext<ParserRuleContext>(context.ModuleName, context.Context)));
4140
}
4241

RetailCoder.VBE/Inspections/QuickFixes/RemoveCommentQuickFix.cs

Lines changed: 16 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,8 @@
11
using Antlr4.Runtime;
22
using Rubberduck.Inspections.Abstract;
33
using Rubberduck.Inspections.Resources;
4+
using Rubberduck.Parsing;
5+
using Rubberduck.Parsing.Grammar;
46
using Rubberduck.Parsing.Symbols;
57
using Rubberduck.Parsing.VBA;
68
using Rubberduck.VBEditor;
@@ -9,43 +11,27 @@ namespace Rubberduck.Inspections.QuickFixes
911
{
1012
public class RemoveCommentQuickFix : QuickFixBase
1113
{
12-
private readonly CommentNode _comment;
13-
14-
public RemoveCommentQuickFix(ParserRuleContext context, QualifiedSelection selection, CommentNode comment)
15-
: base(context, selection, InspectionsUI.RemoveCommentQuickFix)
16-
{
17-
_comment = comment;
18-
}
14+
public RemoveCommentQuickFix(ParserRuleContext context, QualifiedSelection selection)
15+
: base(context, selection, InspectionsUI.RemoveObsoleteStatementQuickFix)
16+
{ }
1917

2018
public override void Fix()
2119
{
2220
var module = Selection.QualifiedName.Component.CodeModule;
23-
{
24-
if (module.IsWrappingNullReference)
25-
{
26-
return;
27-
}
28-
29-
var content = module.GetLines(Selection.Selection.StartLine, Selection.Selection.LineCount);
3021

31-
int markerPosition;
32-
if (!content.HasComment(out markerPosition))
33-
{
34-
return;
35-
}
36-
37-
var code = string.Empty;
38-
if (markerPosition > 0)
39-
{
40-
code = content.Substring(0, markerPosition).TrimEnd();
41-
}
22+
if (module.IsWrappingNullReference)
23+
{
24+
return;
25+
}
4226

43-
if (_comment.QualifiedSelection.Selection.LineCount > 1)
44-
{
45-
module.DeleteLines(_comment.QualifiedSelection.Selection.StartLine, _comment.QualifiedSelection.Selection.LineCount);
46-
}
27+
var start = Context.Start.Line;
28+
var commentLine = module.GetLines(start, Selection.Selection.LineCount);
29+
var newLine = commentLine.Substring(0, Context.Start.Column).TrimEnd();
4730

48-
module.ReplaceLine(_comment.QualifiedSelection.Selection.StartLine, code);
31+
module.DeleteLines(start, Selection.Selection.LineCount);
32+
if (newLine.TrimStart().Length > 0)
33+
{
34+
module.InsertLines(start, newLine);
4935
}
5036
}
5137
}

RetailCoder.VBE/Inspections/QuickFixes/ReplaceObsoleteCommentMarkerQuickFix.cs

Lines changed: 14 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -10,46 +10,26 @@ namespace Rubberduck.Inspections.QuickFixes
1010
{
1111
public class ReplaceObsoleteCommentMarkerQuickFix : QuickFixBase
1212
{
13-
private readonly CommentNode _comment;
14-
15-
public ReplaceObsoleteCommentMarkerQuickFix(ParserRuleContext context, QualifiedSelection selection, CommentNode comment)
16-
: base(context, selection, InspectionsUI.ReplaceCommentMarkerQuickFix)
17-
{
18-
_comment = comment;
19-
}
13+
public ReplaceObsoleteCommentMarkerQuickFix(ParserRuleContext context, QualifiedSelection selection)
14+
: base(context, selection, InspectionsUI.RemoveObsoleteStatementQuickFix)
15+
{ }
2016

2117
public override void Fix()
2218
{
2319
var module = Selection.QualifiedName.Component.CodeModule;
24-
{
25-
if (module.IsWrappingNullReference)
26-
{
27-
return;
28-
}
29-
30-
var content = module.GetLines(Selection.Selection.StartLine, Selection.Selection.LineCount);
3120

32-
int markerPosition;
33-
if (!content.HasComment(out markerPosition))
34-
{
35-
return;
36-
}
37-
38-
var code = string.Empty;
39-
if (markerPosition > 0)
40-
{
41-
code = content.Substring(0, markerPosition);
42-
}
43-
44-
var newContent = code + Tokens.CommentMarker + " " + _comment.CommentText;
45-
46-
if (_comment.QualifiedSelection.Selection.LineCount > 1)
47-
{
48-
module.DeleteLines(_comment.QualifiedSelection.Selection.StartLine + 1, _comment.QualifiedSelection.Selection.LineCount);
49-
}
50-
51-
module.ReplaceLine(Selection.Selection.StartLine, newContent);
21+
if (module.IsWrappingNullReference)
22+
{
23+
return;
5224
}
25+
var comment = Context.GetText();
26+
var start = Context.Start.Line;
27+
var commentLine = module.GetLines(start, 1);
28+
var newComment = commentLine.Substring(0, Context.Start.Column) +
29+
Tokens.CommentMarker +
30+
comment.Substring(Tokens.Rem.Length, comment.Length - Tokens.Rem.Length);
31+
32+
module.ReplaceLine(start, newComment);
5333
}
5434
}
5535
}

RetailCoder.VBE/Inspections/Results/ObsoleteCommentSyntaxInspectionResult.cs

Lines changed: 7 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,30 +1,28 @@
11
using System.Collections.Generic;
2+
using Antlr4.Runtime;
23
using Rubberduck.Inspections.Abstract;
34
using Rubberduck.Inspections.QuickFixes;
45
using Rubberduck.Inspections.Resources;
5-
using Rubberduck.Parsing.Symbols;
6+
using Rubberduck.Parsing;
67

78
namespace Rubberduck.Inspections.Results
89
{
910
public class ObsoleteCommentSyntaxInspectionResult : InspectionResultBase
1011
{
1112
private IEnumerable<QuickFixBase> _quickFixes;
12-
private readonly CommentNode _comment;
1313

14-
public ObsoleteCommentSyntaxInspectionResult(IInspection inspection, CommentNode comment)
15-
: base(inspection, comment)
16-
{
17-
_comment = comment;
18-
}
14+
public ObsoleteCommentSyntaxInspectionResult(IInspection inspection, QualifiedContext<ParserRuleContext> qualifiedContext)
15+
: base(inspection, qualifiedContext.ModuleName, qualifiedContext.Context)
16+
{ }
1917

2018
public override IEnumerable<QuickFixBase> QuickFixes
2119
{
2220
get
2321
{
2422
return _quickFixes ?? (_quickFixes = new QuickFixBase[]
2523
{
26-
new ReplaceObsoleteCommentMarkerQuickFix(Context, QualifiedSelection, _comment),
27-
new RemoveCommentQuickFix(Context, QualifiedSelection, _comment),
24+
new ReplaceObsoleteCommentMarkerQuickFix(Context, QualifiedSelection),
25+
new RemoveCommentQuickFix(Context, QualifiedSelection),
2826
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
2927
});
3028
}

Rubberduck.Parsing/Grammar/VBAParser.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -18626,14 +18626,14 @@ public CommentOrAnnotationContext commentOrAnnotation() {
1862618626
case 2:
1862718627
EnterOuterAlt(_localctx, 2);
1862818628
{
18629-
State = 2665; comment();
18629+
State = 2665; remComment();
1863018630
}
1863118631
break;
1863218632

1863318633
case 3:
1863418634
EnterOuterAlt(_localctx, 3);
1863518635
{
18636-
State = 2666; remComment();
18636+
State = 2666; comment();
1863718637
}
1863818638
break;
1863918639
}
@@ -20742,7 +20742,7 @@ private bool upperCaseA_sempred(UpperCaseAContext _localctx, int predIndex) {
2074220742
"\xA66\x3\x2\x2\x2\xA65\xA5D\x3\x2\x2\x2\xA65\xA5F\x3\x2\x2\x2\xA66\xA69"+
2074320743
"\x3\x2\x2\x2\xA67\xA65\x3\x2\x2\x2\xA67\xA68\x3\x2\x2\x2\xA68\x1A1\x3"+
2074420744
"\x2\x2\x2\xA69\xA67\x3\x2\x2\x2\xA6A\xA6E\x5\x1AA\xD6\x2\xA6B\xA6E\x5"+
20745-
"\x1A6\xD4\x2\xA6C\xA6E\x5\x1A4\xD3\x2\xA6D\xA6A\x3\x2\x2\x2\xA6D\xA6B"+
20745+
"\x1A4\xD3\x2\xA6C\xA6E\x5\x1A6\xD4\x2\xA6D\xA6A\x3\x2\x2\x2\xA6D\xA6B"+
2074620746
"\x3\x2\x2\x2\xA6D\xA6C\x3\x2\x2\x2\xA6E\x1A3\x3\x2\x2\x2\xA6F\xA71\a\xAF"+
2074720747
"\x2\x2\xA70\xA72\x5\x1B6\xDC\x2\xA71\xA70\x3\x2\x2\x2\xA71\xA72\x3\x2"+
2074820748
"\x2\x2\xA72\xA73\x3\x2\x2\x2\xA73\xA74\x5\x1A8\xD5\x2\xA74\x1A5\x3\x2"+

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -844,8 +844,8 @@ endOfStatement :
844844
// Annotations must come before comments because of precedence. ANTLR4 matches as much as possible then chooses the one that comes first.
845845
commentOrAnnotation :
846846
annotationList
847-
| comment
848847
| remComment
848+
| comment
849849
;
850850
remComment : REM whiteSpace? commentBody;
851851
comment : SINGLEQUOTE commentBody;

0 commit comments

Comments
 (0)