Skip to content

Commit 413de06

Browse files
committed
Revert order of attributes pass and code pane pass, and some refactoring.
1 parent d4cd583 commit 413de06

File tree

5 files changed

+39
-49
lines changed

5 files changed

+39
-49
lines changed

Rubberduck.Parsing/VBA/AttributeParser.cs

Lines changed: 9 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -26,18 +26,15 @@ public AttributeParser(IModuleExporter exporter, Func<IVBAPreprocessor> preproce
2626
/// Exports the specified component to a temporary file, loads, and then parses the exported file.
2727
/// </summary>
2828
/// <param name="component"></param>
29-
/// <param name="token"></param>
30-
/// <param name="stream"></param>
31-
public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponent component, CancellationToken token, out ITokenStream stream, out IParseTree tree)
29+
/// <param name="cancellationToken"></param>
30+
public (IParseTree tree, ITokenStream tokenStream, IDictionary<Tuple<string, DeclarationType>, Attributes> attributes) Parse(IVBComponent component, CancellationToken cancellationToken)
3231
{
33-
token.ThrowIfCancellationRequested();
32+
cancellationToken.ThrowIfCancellationRequested();
3433
var path = _exporter.Export(component);
3534
if (!File.Exists(path))
3635
{
3736
// a document component without any code wouldn't be exported (file would be empty anyway).
38-
stream = null;
39-
tree = null;
40-
return new Dictionary<Tuple<string, DeclarationType>, Attributes>();
37+
return (null, null, new Dictionary<Tuple<string, DeclarationType>, Attributes>());
4138
}
4239
var code = File.ReadAllText(path);
4340
try
@@ -49,24 +46,24 @@ public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponen
4946
// Meh.
5047
}
5148

52-
token.ThrowIfCancellationRequested();
49+
cancellationToken.ThrowIfCancellationRequested();
5350

5451
var type = component.Type == ComponentType.StandardModule
5552
? DeclarationType.ProceduralModule
5653
: DeclarationType.ClassModule;
5754
var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider();
5855
var tokens = tokenStreamProvider.Tokens(code);
5956
var preprocessor = _preprocessorFactory();
60-
preprocessor.PreprocessTokenStream(component.Name, tokens, token);
57+
preprocessor.PreprocessTokenStream(component.Name, tokens, cancellationToken);
6158
var listener = new AttributeListener(Tuple.Create(component.Name, type));
6259
// parse tree isn't usable for declarations because
6360
// line numbers are offset due to module header and attributes
6461
// (these don't show up in the VBE, that's why we're parsing an exported file)
6562

66-
tree = new VBAModuleParser().Parse(component.Name, tokens, new IParseTreeListener[] { listener }, new ExceptionErrorListener(), out stream);
63+
var parseResults = new VBAModuleParser().Parse(component.Name, tokens, new IParseTreeListener[] { listener }, new ExceptionErrorListener());
6764

68-
token.ThrowIfCancellationRequested();
69-
return listener.Attributes;
65+
cancellationToken.ThrowIfCancellationRequested();
66+
return (parseResults.tree, parseResults.tokenStream, listener.Attributes);
7067
}
7168
}
7269
}

Rubberduck.Parsing/VBA/ComponentParseTask.cs

Lines changed: 22 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -47,44 +47,40 @@ public ComponentParseTask(QualifiedModuleName module, IVBAPreprocessor preproces
4747
_parser = new VBAModuleParser();
4848
}
4949

50-
public void Start(CancellationToken token)
50+
public void Start(CancellationToken cancellationToken)
5151
{
5252
try
5353
{
5454
Logger.Trace($"Starting ParseTaskID {_taskId} on thread {Thread.CurrentThread.ManagedThreadId}.");
5555

56-
var tokenStream = RewriteAndPreprocess(token);
57-
token.ThrowIfCancellationRequested();
58-
59-
IParseTree attributesTree;
60-
IDictionary<Tuple<string, DeclarationType>, Attributes> attributes;
61-
var attributesTokenStream = RunAttributesPass(token, out attributesTree, out attributes);
62-
63-
var rewriter = new MemberAttributesRewriter(_exporter, _component.CodeModule, new TokenStreamRewriter(attributesTokenStream ?? tokenStream));
56+
var tokenStream = RewriteAndPreprocess(cancellationToken);
57+
cancellationToken.ThrowIfCancellationRequested();
6458

6559
// temporal coupling... comments must be acquired before we walk the parse tree for declarations
6660
// otherwise none of the annotations get associated to their respective Declaration
6761
var commentListener = new CommentListener();
6862
var annotationListener = new AnnotationListener(new VBAParserAnnotationFactory(), _qualifiedName);
6963

7064
var stopwatch = Stopwatch.StartNew();
71-
ITokenStream stream;
72-
var tree = ParseInternal(_component.Name, tokenStream, new IParseTreeListener[]{ commentListener, annotationListener }, out stream);
65+
var codePaneParseResults = ParseInternal(_component.Name, tokenStream, new IParseTreeListener[]{ commentListener, annotationListener });
7366
stopwatch.Stop();
74-
token.ThrowIfCancellationRequested();
67+
cancellationToken.ThrowIfCancellationRequested();
7568

7669
var comments = QualifyAndUnionComments(_qualifiedName, commentListener.Comments, commentListener.RemComments);
77-
token.ThrowIfCancellationRequested();
70+
cancellationToken.ThrowIfCancellationRequested();
71+
72+
var attributesPassParseResults = RunAttributesPass(cancellationToken);
73+
var rewriter = new MemberAttributesRewriter(_exporter, _component.CodeModule, new TokenStreamRewriter(attributesPassParseResults.tokenStream ?? tokenStream));
7874

7975
var completedHandler = ParseCompleted;
80-
if (completedHandler != null && !token.IsCancellationRequested)
76+
if (completedHandler != null && !cancellationToken.IsCancellationRequested)
8177
completedHandler.Invoke(this, new ParseCompletionArgs
8278
{
83-
ParseTree = tree,
84-
AttributesTree = attributesTree,
85-
Tokens = stream,
79+
ParseTree = codePaneParseResults.tree,
80+
AttributesTree = attributesPassParseResults.tree,
81+
Tokens = codePaneParseResults.tokenStream,
8682
AttributesRewriter = rewriter,
87-
Attributes = attributes,
83+
Attributes = attributesPassParseResults.attributes,
8884
Comments = comments,
8985
Annotations = annotationListener.Annotations
9086
});
@@ -128,14 +124,12 @@ public void Start(CancellationToken token)
128124
}
129125
}
130126

131-
private ITokenStream RunAttributesPass(CancellationToken token, out IParseTree attributesTree,
132-
out IDictionary<Tuple<string, DeclarationType>, Attributes> attributes)
127+
private (IParseTree tree, ITokenStream tokenStream, IDictionary<Tuple<string, DeclarationType>, Attributes> attributes) RunAttributesPass(CancellationToken cancellationToken)
133128
{
134129
Logger.Trace($"ParseTaskID {_taskId} begins attributes pass.");
135-
ITokenStream attributesTokenStream;
136-
attributes = _attributeParser.Parse(_component, token, out attributesTokenStream, out attributesTree);
130+
var attributesParseResults = _attributeParser.Parse(_component, cancellationToken);
137131
Logger.Trace($"ParseTaskID {_taskId} finished attributes pass.");
138-
return attributesTokenStream;
132+
return attributesParseResults;
139133
}
140134

141135
private static string GetCode(ICodeModule module)
@@ -152,20 +146,20 @@ private static string GetCode(ICodeModule module)
152146
return code;
153147
}
154148

155-
private CommonTokenStream RewriteAndPreprocess(CancellationToken token)
149+
private CommonTokenStream RewriteAndPreprocess(CancellationToken cancellationToken)
156150
{
157-
var code = _rewriter == null ? string.Join(Environment.NewLine, GetCode(_component.CodeModule)) : _rewriter.GetText();
151+
var code = _rewriter?.GetText() ?? string.Join(Environment.NewLine, GetCode(_component.CodeModule));
158152
var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider();
159153
var tokens = tokenStreamProvider.Tokens(code);
160-
_preprocessor.PreprocessTokenStream(_component.Name, tokens, token);
154+
_preprocessor.PreprocessTokenStream(_component.Name, tokens, cancellationToken);
161155
return tokens;
162156
}
163157

164-
private IParseTree ParseInternal(string moduleName, CommonTokenStream tokenStream, IParseTreeListener[] listeners, out ITokenStream outStream)
158+
private (IParseTree tree, ITokenStream tokenStream) ParseInternal(string moduleName, CommonTokenStream tokenStream, IParseTreeListener[] listeners)
165159
{
166160
//var errorNotifier = new SyntaxErrorNotificationListener();
167161
//errorNotifier.OnSyntaxError += ParserSyntaxError;
168-
return _parser.Parse(moduleName, tokenStream, listeners, new ExceptionErrorListener(), out outStream);
162+
return _parser.Parse(moduleName, tokenStream, listeners, new ExceptionErrorListener());
169163
}
170164

171165
private IEnumerable<CommentNode> QualifyAndUnionComments(QualifiedModuleName qualifiedName, IEnumerable<VBAParser.CommentContext> comments, IEnumerable<VBAParser.RemCommentContext> remComments)

Rubberduck.Parsing/VBA/IAttributeParser.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,6 @@ namespace Rubberduck.Parsing.VBA
1010
{
1111
public interface IAttributeParser
1212
{
13-
IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponent component, CancellationToken token, out ITokenStream stream, out IParseTree tree);
13+
(IParseTree tree, ITokenStream tokenStream, IDictionary<Tuple<string, DeclarationType>, Attributes> attributes) Parse(IVBComponent component, CancellationToken cancellationToken);
1414
}
1515
}

Rubberduck.Parsing/VBA/VBAModuleParser.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@ public sealed class VBAModuleParser
1111
{
1212
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
1313

14-
public IParseTree Parse(string moduleName, CommonTokenStream moduleTokens, IParseTreeListener[] listeners, BaseErrorListener errorListener, out ITokenStream outStream)
14+
public (IParseTree tree, ITokenStream tokenStream) Parse(string moduleName, CommonTokenStream moduleTokens, IParseTreeListener[] listeners, BaseErrorListener errorListener)
1515
{
1616
moduleTokens.Reset();
1717
var parser = new VBAParser(moduleTokens);
@@ -34,8 +34,7 @@ public IParseTree Parse(string moduleName, CommonTokenStream moduleTokens, IPars
3434
{
3535
ParseTreeWalker.Default.Walk(listener, tree);
3636
}
37-
outStream = moduleTokens;
38-
return tree;
37+
return (tree, moduleTokens);
3938
}
4039
}
4140
}

RubberduckTests/Mocks/TestAttributeParser.cs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ public TestAttributeParser(Func<IVBAPreprocessor> preprocessorFactory)
1919
_preprocessorFactory = preprocessorFactory;
2020
}
2121

22-
public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponent component, CancellationToken token, out ITokenStream stream, out IParseTree tree)
22+
public (IParseTree tree, ITokenStream tokenStream, IDictionary<Tuple<string, DeclarationType>, Attributes> attributes) Parse(IVBComponent component, CancellationToken cancellationToken)
2323
{
2424
var code = component.CodeModule.Content();
2525
var type = component.Type == ComponentType.StandardModule
@@ -28,16 +28,16 @@ public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponen
2828
var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider();
2929
var tokens = tokenStreamProvider.Tokens(code);
3030
var preprocessor = _preprocessorFactory();
31-
preprocessor.PreprocessTokenStream(component.Name, tokens, token);
31+
preprocessor.PreprocessTokenStream(component.Name, tokens, cancellationToken);
3232
var listener = new AttributeListener(Tuple.Create(component.Name, type));
3333
// parse tree isn't usable for declarations because
3434
// line numbers are offset due to module header and attributes
3535
// (these don't show up in the VBE, that's why we're parsing an exported file)
3636

37-
tree = new VBAModuleParser().Parse(component.Name, tokens, new IParseTreeListener[] { listener }, new ExceptionErrorListener(), out stream);
37+
var parseResults = new VBAModuleParser().Parse(component.Name, tokens, new IParseTreeListener[] { listener }, new ExceptionErrorListener());
3838

39-
token.ThrowIfCancellationRequested();
40-
return listener.Attributes;
39+
cancellationToken.ThrowIfCancellationRequested();
40+
return (parseResults.tree, parseResults.tokenStream, listener.Attributes);
4141
}
4242
}
4343
}

0 commit comments

Comments
 (0)