Skip to content

Commit 5dd97be

Browse files
committed
Merge branch 'rubberduck-vba-next' of https://github.com/retailcoder/Rubberduck into rubberduck-vba-next
2 parents c52b70b + f8b6d33 commit 5dd97be

9 files changed

+669
-76
lines changed

Rubberduck.Parsing/IRubberduckParser.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,8 @@ public interface IRubberduckParser
1010
{
1111
RubberduckParserState State { get; }
1212
void ParseComponent(VBComponent component, TokenStreamRewriter rewriter = null);
13-
//Task ParseAsync(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null);
14-
//void Resolve(CancellationToken token);
13+
Task ParseAsync(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null);
14+
void Cancel(VBComponent component = null);
15+
void Resolve(CancellationToken token);
1516
}
1617
}

Rubberduck.Parsing/Rubberduck.Parsing.csproj

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -179,6 +179,8 @@
179179
<Compile Include="Symbols\ValuedDeclaration.cs" />
180180
<Compile Include="VBA\AttributeParser.cs" />
181181
<Compile Include="VBA\Attributes.cs" />
182+
<Compile Include="VBA\CombinedParseTreeListener.cs" />
183+
<Compile Include="VBA\ComponentParseTask.cs" />
182184
<Compile Include="VBA\EnumerableExtensions.cs" />
183185
<Compile Include="VBA\IAttributeParser.cs" />
184186
<Compile Include="VBA\IModuleExporter.cs" />
@@ -188,6 +190,7 @@
188190
<Compile Include="VBA\ParseErrorEventArgs.cs" />
189191
<Compile Include="VBA\ParserState.cs" />
190192
<Compile Include="VBA\RubberduckParser.cs" />
193+
<Compile Include="VBA\RubberduckParserReimpl.cs" />
191194
<Compile Include="VBA\RubberduckParserState.cs" />
192195
<Compile Include="VBA\StringExtensions.cs" />
193196
<Compile Include="VBA\WalkerCancelledException.cs" />
Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,39 @@
1+
using Antlr4.Runtime;
2+
using Antlr4.Runtime.Tree;
3+
using System.Collections.Generic;
4+
using System.Linq;
5+
6+
namespace Rubberduck.Parsing.VBA
7+
{
8+
/// <summary>
9+
/// A Class combining an arbitrary number of IParseTreeListener instances into one single instance
10+
/// </summary>
11+
public class CombinedParseTreeListener : IParseTreeListener
12+
{
13+
private List<IParseTreeListener> _listeners;
14+
public CombinedParseTreeListener(IParseTreeListener[] listeners)
15+
{
16+
_listeners = listeners.ToList();
17+
}
18+
19+
public void EnterEveryRule(ParserRuleContext ctx)
20+
{
21+
_listeners.ForEach(l => l.EnterEveryRule(ctx));
22+
}
23+
24+
public void ExitEveryRule(ParserRuleContext ctx)
25+
{
26+
_listeners.ForEach(l => l.ExitEveryRule(ctx));
27+
}
28+
29+
public void VisitErrorNode(IErrorNode node)
30+
{
31+
_listeners.ForEach(l => l.VisitErrorNode(node));
32+
}
33+
34+
public void VisitTerminal(ITerminalNode node)
35+
{
36+
_listeners.ForEach(l => l.VisitTerminal(node));
37+
}
38+
}
39+
}
Lines changed: 173 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,173 @@
1+
using Antlr4.Runtime;
2+
using Antlr4.Runtime.Misc;
3+
using Antlr4.Runtime.Tree;
4+
using Microsoft.Vbe.Interop;
5+
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.Parsing.Nodes;
7+
using Rubberduck.Parsing.Preprocessing;
8+
using Rubberduck.Parsing.Symbols;
9+
using Rubberduck.VBEditor;
10+
using Rubberduck.VBEditor.Extensions;
11+
using System;
12+
using System.Collections.Generic;
13+
using System.Diagnostics;
14+
using System.Linq;
15+
using System.Runtime.InteropServices;
16+
using System.Threading;
17+
using System.Threading.Tasks;
18+
19+
namespace Rubberduck.Parsing.VBA
20+
{
21+
class ComponentParseTask
22+
{
23+
private readonly VBComponent _component;
24+
private readonly QualifiedModuleName _qualifiedName;
25+
private readonly TokenStreamRewriter _rewriter;
26+
private readonly IAttributeParser _attributeParser;
27+
private readonly VBAPreprocessor _preprocessor;
28+
29+
public event EventHandler<ParseCompletionArgs> ParseCompleted;
30+
public event EventHandler<ParseFailureArgs> ParseFailure;
31+
32+
public ComponentParseTask(VBComponent vbComponent, VBAPreprocessor preprocessor, IAttributeParser attributeParser, TokenStreamRewriter rewriter = null)
33+
{
34+
_attributeParser = attributeParser;
35+
_preprocessor = preprocessor;
36+
_component = vbComponent;
37+
_rewriter = rewriter;
38+
_qualifiedName = new QualifiedModuleName(vbComponent);
39+
}
40+
41+
public void Start(CancellationToken token)
42+
{
43+
try
44+
{
45+
var code = RewriteAndPreprocess();
46+
token.ThrowIfCancellationRequested();
47+
48+
var attributes = _attributeParser.Parse(_component);
49+
50+
token.ThrowIfCancellationRequested();
51+
52+
// temporal coupling... comments must be acquired before we walk the parse tree for declarations
53+
// otherwise none of the annotations get associated to their respective Declaration
54+
var commentListener = new CommentListener();
55+
56+
var stopwatch = Stopwatch.StartNew();
57+
ITokenStream stream;
58+
var tree = ParseInternal(code, new IParseTreeListener[]{ commentListener }, out stream);
59+
stopwatch.Stop();
60+
if (tree != null)
61+
{
62+
Debug.Print("IParseTree for component '{0}' acquired in {1}ms (thread {2})", _component.Name, stopwatch.ElapsedMilliseconds, Thread.CurrentThread.ManagedThreadId);
63+
}
64+
65+
var comments = QualifyAndUnionComments(_qualifiedName, commentListener.Comments, commentListener.RemComments);
66+
token.ThrowIfCancellationRequested();
67+
68+
ParseCompleted.Invoke(this, new ParseCompletionArgs
69+
{
70+
ParseTree = tree,
71+
Tokens = stream,
72+
Attributes = attributes,
73+
Comments = comments,
74+
});
75+
}
76+
catch (COMException exception)
77+
{
78+
Debug.WriteLine("Exception thrown in thread {0}:\n{1}", Thread.CurrentThread.ManagedThreadId, exception);
79+
ParseFailure.Invoke(this, new ParseFailureArgs
80+
{
81+
Cause = exception
82+
});
83+
}
84+
catch (SyntaxErrorException exception)
85+
{
86+
Debug.WriteLine("Exception thrown in thread {0}:\n{1}", Thread.CurrentThread.ManagedThreadId, exception);
87+
ParseFailure.Invoke(this, new ParseFailureArgs
88+
{
89+
Cause = exception
90+
});
91+
}
92+
catch (OperationCanceledException cancel)
93+
{
94+
Debug.WriteLine("Operation was Cancelled", cancel);
95+
// no results to be used, so no results "returned"
96+
//ParseCompleted.Invoke(this, new ParseCompletionArgs());
97+
}
98+
}
99+
100+
private string RewriteAndPreprocess()
101+
{
102+
var code = _rewriter == null ? string.Join(Environment.NewLine, _component.CodeModule.GetSanitizedCode()) : _rewriter.GetText();
103+
string processed;
104+
try
105+
{
106+
processed = _preprocessor.Execute(code);
107+
}
108+
catch (VBAPreprocessorException)
109+
{
110+
Debug.WriteLine("Falling back to no preprocessing");
111+
processed = code;
112+
}
113+
return processed;
114+
}
115+
116+
private static IParseTree ParseInternal(string code, IParseTreeListener[] listeners, out ITokenStream outStream)
117+
{
118+
var stream = new AntlrInputStream(code);
119+
var lexer = new VBALexer(stream);
120+
var tokens = new CommonTokenStream(lexer);
121+
var parser = new VBAParser(tokens);
122+
123+
parser.AddErrorListener(new ExceptionErrorListener());
124+
foreach (var l in listeners)
125+
{
126+
parser.AddParseListener(l);
127+
}
128+
129+
outStream = tokens;
130+
return parser.startRule();
131+
}
132+
133+
private IEnumerable<CommentNode> QualifyAndUnionComments(QualifiedModuleName qualifiedName, IEnumerable<VBAParser.CommentContext> comments, IEnumerable<VBAParser.RemCommentContext> remComments)
134+
{
135+
var commentNodes = comments.Select(comment => new CommentNode(comment.GetComment(), Tokens.CommentMarker, new QualifiedSelection(qualifiedName, comment.GetSelection())));
136+
var remCommentNodes = remComments.Select(comment => new CommentNode(comment.GetComment(), Tokens.Rem, new QualifiedSelection(qualifiedName, comment.GetSelection())));
137+
var allCommentNodes = commentNodes.Union(remCommentNodes);
138+
return allCommentNodes;
139+
}
140+
141+
public class ParseCompletionArgs
142+
{
143+
public ITokenStream Tokens { get; internal set; }
144+
public IParseTree ParseTree { get; internal set; }
145+
public IDictionary<Tuple<string, DeclarationType>, Attributes> Attributes { get; internal set; }
146+
public IEnumerable<CommentNode> Comments { get; internal set; }
147+
}
148+
149+
public class ParseFailureArgs
150+
{
151+
public Exception Cause { get; internal set; }
152+
}
153+
154+
private class CommentListener : VBAParserBaseListener
155+
{
156+
private readonly IList<VBAParser.RemCommentContext> _remComments = new List<VBAParser.RemCommentContext>();
157+
public IEnumerable<VBAParser.RemCommentContext> RemComments { get { return _remComments; } }
158+
159+
private readonly IList<VBAParser.CommentContext> _comments = new List<VBAParser.CommentContext>();
160+
public IEnumerable<VBAParser.CommentContext> Comments { get { return _comments; } }
161+
162+
public override void ExitRemComment([NotNull] VBAParser.RemCommentContext context)
163+
{
164+
_remComments.Add(context);
165+
}
166+
167+
public override void ExitComment([NotNull] VBAParser.CommentContext context)
168+
{
169+
_comments.Add(context);
170+
}
171+
}
172+
}
173+
}

Rubberduck.Parsing/VBA/ParserState.cs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -5,34 +5,34 @@ public enum ParserState
55
/// <summary>
66
/// Parse was requested but hasn't started yet.
77
/// </summary>
8-
Pending,
8+
Pending = 0,
99
/// <summary>
1010
/// Project references are being loaded into parser state.
1111
/// </summary>
12-
LoadingReference,
12+
LoadingReference = 1,
1313
/// <summary>
1414
/// Code from modified modules is being parsed.
1515
/// </summary>
16-
Parsing,
16+
Parsing = 2,
1717
/// <summary>
1818
/// Parse tree is waiting to be walked for identifier resolution.
1919
/// </summary>
20-
Parsed,
20+
Parsed = 3,
2121
/// <summary>
2222
/// Resolving identifier references.
2323
/// </summary>
24-
Resolving,
24+
Resolving = 4,
2525
/// <summary>
2626
/// Parser state is in sync with the actual code in the VBE.
2727
/// </summary>
28-
Ready,
28+
Ready = 5,
2929
/// <summary>
3030
/// Parsing could not be completed for one or more modules.
3131
/// </summary>
32-
Error,
32+
Error = 99,
3333
/// <summary>
3434
/// Parsing completed, but identifier references could not be resolved for one or more modules.
3535
/// </summary>
36-
ResolverError,
36+
ResolverError = 6,
3737
}
3838
}

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 24 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -20,11 +20,11 @@
2020

2121
namespace Rubberduck.Parsing.VBA
2222
{
23-
public class RubberduckParser : IRubberduckParser
23+
public class RubberduckParserLegacy : IRubberduckParser
2424
{
2525
private readonly ReferencedDeclarationsCollector _comReflector;
2626

27-
public RubberduckParser(VBE vbe, RubberduckParserState state, IAttributeParser attributeParser)
27+
public RubberduckParserLegacy(VBE vbe, RubberduckParserState state, IAttributeParser attributeParser)
2828
{
2929
_vbe = vbe;
3030
_state = state;
@@ -38,8 +38,8 @@ public RubberduckParser(VBE vbe, RubberduckParserState state, IAttributeParser a
3838

3939
private void ReparseRequested(object sender, EventArgs e)
4040
{
41-
Task.Run(() => ParseInternal());
42-
}
41+
Task.Run(() => ParseInternal());
42+
}
4343

4444
private readonly VBE _vbe;
4545
private readonly RubberduckParserState _state;
@@ -361,6 +361,26 @@ private ParserState WalkParseTree(VBComponent component, IParseTree tree, Declar
361361
return ParserState.Ready;
362362
}
363363

364+
public void Resolve(CancellationToken token)
365+
{
366+
throw new NotImplementedException();
367+
}
368+
369+
public Task ParseAsync(VBComponent component, TokenStreamRewriter rewriter = null)
370+
{
371+
throw new NotImplementedException();
372+
}
373+
374+
public void Cancel(VBComponent component = null)
375+
{
376+
throw new NotImplementedException();
377+
}
378+
379+
public Task ParseAsync(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null)
380+
{
381+
throw new NotImplementedException();
382+
}
383+
364384
private class ObsoleteCallStatementListener : VBAParserBaseListener
365385
{
366386
private readonly IList<VBAParser.ExplicitCallStmtContext> _contexts = new List<VBAParser.ExplicitCallStmtContext>();

0 commit comments

Comments
 (0)