Skip to content

Commit 4a7be5d

Browse files
author
Andrin Meier
committed
migrate comment parsing to parse tree generated nodes
1 parent 43221db commit 4a7be5d

File tree

5 files changed

+21
-65
lines changed

5 files changed

+21
-65
lines changed

RetailCoder.VBE/Inspections/OptionBaseInspectionResult.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
using Rubberduck.Parsing.Grammar;
12
using Rubberduck.Parsing.Nodes;
23
using Rubberduck.VBEditor;
34

@@ -6,7 +7,7 @@ namespace Rubberduck.Inspections
67
public class OptionBaseInspectionResult : InspectionResultBase
78
{
89
public OptionBaseInspectionResult(IInspection inspection, QualifiedModuleName qualifiedName)
9-
: base(inspection, new CommentNode(string.Empty, new QualifiedSelection(qualifiedName, Selection.Home)))
10+
: base(inspection, new CommentNode(string.Empty, Tokens.CommentMarker, new QualifiedSelection(qualifiedName, Selection.Home)))
1011
{
1112
}
1213

RetailCoder.VBE/Inspections/OptionExplicitInspectionResult.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ public class OptionExplicitInspectionResult : InspectionResultBase
1313
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
1414

1515
public OptionExplicitInspectionResult(IInspection inspection, QualifiedModuleName qualifiedName)
16-
: base(inspection, new CommentNode(string.Empty, new QualifiedSelection(qualifiedName, Selection.Home)))
16+
: base(inspection, new CommentNode(string.Empty, Tokens.CommentMarker, new QualifiedSelection(qualifiedName, Selection.Home)))
1717
{
1818
_quickFixes = new[]
1919
{

RetailCoder.VBE/UI/ToDoItems/ToDoExplorerViewModel.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -118,7 +118,7 @@ private IEnumerable<ToDoItem> GetToDoMarkers(CommentNode comment)
118118
{
119119
var markers = _configService.LoadConfiguration().UserSettings.ToDoListSettings.ToDoMarkers;
120120
return markers.Where(marker => !string.IsNullOrEmpty(marker.Text)
121-
&& comment.Comment.ToLowerInvariant().Contains(marker.Text.ToLowerInvariant()))
121+
&& comment.CommentText.ToLowerInvariant().Contains(marker.Text.ToLowerInvariant()))
122122
.Select(marker => new ToDoItem(marker.Text, comment));
123123
}
124124

Rubberduck.Parsing/Nodes/CommentNode.cs

Lines changed: 7 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1,42 +1,32 @@
1-
using System;
2-
using Rubberduck.Parsing.Grammar;
31
using Rubberduck.VBEditor;
42

53
namespace Rubberduck.Parsing.Nodes
64
{
75
/// <summary>
86
/// Represents a comment.
97
/// </summary>
10-
/// <remarks>
11-
/// This is working around the limitations of the .g4 grammar file in use,
12-
/// which ignores comments. Ideally comments would be part of the grammar,
13-
/// and parsed along with the rest of the language syntax into an IParseTree.
14-
/// </remarks>
158
public class CommentNode
169
{
1710
private readonly string _comment;
11+
private readonly string _marker;
1812
private readonly QualifiedSelection _qualifiedSelection;
1913

2014
/// <summary>
2115
/// Creates a new comment node.
2216
/// </summary>
23-
/// <param name="comment">The comment line text, including the comment marker.</param>
17+
/// <param name="comment">The comment line text, without the comment marker.</param>
2418
/// <param name="qualifiedSelection">The information required to locate and select this node in its VBE code pane.</param>
25-
public CommentNode(string comment, QualifiedSelection qualifiedSelection)
19+
public CommentNode(string comment, string marker, QualifiedSelection qualifiedSelection)
2620
{
2721
_comment = comment;
22+
_marker = marker;
2823
_qualifiedSelection = qualifiedSelection;
2924
}
3025

3126
/// <summary>
32-
/// Gets the comment line text, including the comment marker.
27+
/// Gets the comment text, without the comment marker.
3328
/// </summary>
34-
public string Comment { get { return _comment; } }
35-
36-
/// <summary>
37-
/// Gets the trimmed comment text, without the comment marker.
38-
/// </summary>
39-
public string CommentText { get { return _comment.Remove(_comment.IndexOf(Marker, StringComparison.Ordinal), Marker.Length).Trim(); } }
29+
public string CommentText { get { return _comment; } }
4030

4131
/// <summary>
4232
/// The token used to indicate a comment.
@@ -45,9 +35,7 @@ public string Marker
4535
{
4636
get
4737
{
48-
return _comment.StartsWith(Tokens.CommentMarker)
49-
? Tokens.CommentMarker
50-
: Tokens.Rem;
38+
return _marker;
5139
}
5240
}
5341

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 10 additions & 43 deletions
Original file line numberDiff line numberDiff line change
@@ -182,48 +182,14 @@ public void Resolve(CancellationToken token)
182182
}
183183
}
184184

185-
private IEnumerable<CommentNode> ParseComments(QualifiedModuleName qualifiedName)
185+
private IEnumerable<CommentNode> ParseComments(QualifiedModuleName qualifiedName, IEnumerable<VBAParser.CommentContext> comments, IEnumerable<VBAParser.RemCommentContext> remComments)
186186
{
187-
var result = new List<CommentNode>();
188-
189-
var code = qualifiedName.Component.CodeModule.GetSanitizedCode();
190-
var commentBuilder = new StringBuilder();
191-
var continuing = false;
192-
193-
var startLine = 0;
194-
var startColumn = 0;
195-
196-
for (var i = 0; i < code.Length; i++)
197-
{
198-
var line = code[i];
199-
var index = 0;
200-
201-
if (continuing || line.HasComment(out index))
202-
{
203-
startLine = continuing ? startLine : i;
204-
startColumn = continuing ? startColumn : index;
205-
206-
var commentLength = line.Length - index;
207-
208-
continuing = line.EndsWith("_");
209-
if (!continuing)
210-
{
211-
commentBuilder.Append(line.Substring(index, commentLength).TrimStart());
212-
var selection = new Selection(startLine + 1, startColumn + 1, i + 1, line.Length + 1);
213-
214-
var comment = new CommentNode(commentBuilder.ToString(), new QualifiedSelection(qualifiedName, selection));
215-
commentBuilder.Clear();
216-
result.Add(comment);
217-
}
218-
else
219-
{
220-
// ignore line continuations in comment text:
221-
commentBuilder.Append(line.Substring(index, commentLength).TrimStart());
222-
}
223-
}
224-
}
225-
226-
return result;
187+
var commentNodes = comments
188+
.Select(comment => new CommentNode(comment.GetComment(), Tokens.CommentMarker, new QualifiedSelection(qualifiedName, comment.GetSelection())));
189+
var remCommentNodes = remComments
190+
.Select(comment => new CommentNode(comment.GetComment(), Tokens.Rem, new QualifiedSelection(qualifiedName, comment.GetSelection())));
191+
var allCommentNodes = commentNodes.Union(remCommentNodes);
192+
return allCommentNodes;
227193
}
228194

229195
private void ParseInternal(VBComponent vbComponent, string code, CancellationToken token)
@@ -232,8 +198,6 @@ private void ParseInternal(VBComponent vbComponent, string code, CancellationTok
232198
State.SetModuleState(vbComponent, ParserState.Parsing);
233199

234200
var qualifiedName = new QualifiedModuleName(vbComponent);
235-
var comments = ParseComments(qualifiedName);
236-
_state.SetModuleComments(vbComponent, comments);
237201

238202
var obsoleteCallsListener = new ObsoleteCallStatementListener();
239203
var obsoleteLetListener = new ObsoleteLetStatementListener();
@@ -273,6 +237,9 @@ private void ParseInternal(VBComponent vbComponent, string code, CancellationTok
273237
walker.Walk(declarationsListener, tree);
274238
declarationsListener.NewDeclaration -= declarationsListener_NewDeclaration;
275239

240+
var comments = ParseComments(qualifiedName, commentListener.Comments, commentListener.RemComments);
241+
_state.SetModuleComments(vbComponent, comments);
242+
276243
_state.ObsoleteCallContexts = obsoleteCallsListener.Contexts.Select(context => new QualifiedContext(qualifiedName, context));
277244
_state.ObsoleteLetContexts = obsoleteLetListener.Contexts.Select(context => new QualifiedContext(qualifiedName, context));
278245
_state.EmptyStringLiterals = emptyStringLiteralListener.Contexts.Select(context => new QualifiedContext(qualifiedName, context));

0 commit comments

Comments
 (0)