|
| 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 IParseTreeListener[] _listeners; |
| 24 | + |
| 25 | + private readonly VBComponent _component; |
| 26 | + private readonly QualifiedModuleName _qualifiedName; |
| 27 | + private readonly TokenStreamRewriter _rewriter; |
| 28 | + private readonly IAttributeParser _attributeParser; |
| 29 | + private readonly VBAPreprocessor _preprocessor; |
| 30 | + |
| 31 | + public event EventHandler<ParseCompletionArgs> ParseCompleted; |
| 32 | + public event EventHandler<ParseFailureArgs> ParseFailure; |
| 33 | + |
| 34 | + public ComponentParseTask(VBComponent vbComponent, VBAPreprocessor preprocessor, IAttributeParser attributeParser, TokenStreamRewriter rewriter = null) |
| 35 | + { |
| 36 | + _component = vbComponent; |
| 37 | + _listeners = new IParseTreeListener[] |
| 38 | + { |
| 39 | + new ObsoleteCallStatementListener(), |
| 40 | + new ObsoleteLetStatementListener(), |
| 41 | + new EmptyStringLiteralListener(), |
| 42 | + new ArgListWithOneByRefParamListener(), |
| 43 | + new CommentListener(), |
| 44 | + }; |
| 45 | + _rewriter = rewriter; |
| 46 | + _qualifiedName = new QualifiedModuleName(vbComponent); |
| 47 | + } |
| 48 | + |
| 49 | + public Task ParseAsync(CancellationToken token) |
| 50 | + { |
| 51 | + return new Task(() => ParseInternal(token)); |
| 52 | + } |
| 53 | + |
| 54 | + private void ParseInternal(CancellationToken token) |
| 55 | + { |
| 56 | + try |
| 57 | + { |
| 58 | + var code = RewriteAndPreprocess(); |
| 59 | + token.ThrowIfCancellationRequested(); |
| 60 | + |
| 61 | + var stopwatch = Stopwatch.StartNew(); |
| 62 | + ITokenStream stream; |
| 63 | + var tree = ParseInternal(code, _listeners, out stream); |
| 64 | + stopwatch.Stop(); |
| 65 | + if (tree != null) |
| 66 | + { |
| 67 | + Debug.Print("IParseTree for component '{0}' acquired in {1}ms (thread {2})", _component.Name, stopwatch.ElapsedMilliseconds, Thread.CurrentThread.ManagedThreadId); |
| 68 | + } |
| 69 | + |
| 70 | + token.ThrowIfCancellationRequested(); |
| 71 | + |
| 72 | + var attributes = _attributeParser.Parse(_component); |
| 73 | + CommentListener commentListener = _listeners.OfType<CommentListener>().Single(); |
| 74 | + var comments = ParseComments(_qualifiedName, commentListener.Comments, commentListener.RemComments); |
| 75 | + |
| 76 | + token.ThrowIfCancellationRequested(); |
| 77 | + |
| 78 | + var obsoleteCallsListener = _listeners.OfType<ObsoleteCallStatementListener>().Single(); |
| 79 | + var obsoleteLetListener = _listeners.OfType<ObsoleteLetStatementListener>().Single(); |
| 80 | + var emptyStringLiteralListener = _listeners.OfType<EmptyStringLiteralListener>().Single(); |
| 81 | + var argListsWithOneByRefParamListener = _listeners.OfType<ArgListWithOneByRefParamListener>().Single(); |
| 82 | + |
| 83 | + ParseCompleted.Invoke(this, new ParseCompletionArgs |
| 84 | + { |
| 85 | + Comments = comments, |
| 86 | + ParseTree = tree, |
| 87 | + Tokens = stream, |
| 88 | + Attributes = attributes, |
| 89 | + ObsoleteCallContexts = obsoleteCallsListener.Contexts.Select(context => new QualifiedContext(_qualifiedName, context)), |
| 90 | + ObsoleteLetContexts = obsoleteLetListener.Contexts.Select(context => new QualifiedContext(_qualifiedName, context)), |
| 91 | + EmptyStringLiterals = emptyStringLiteralListener.Contexts.Select(context => new QualifiedContext(_qualifiedName, context)), |
| 92 | + ArgListsWithOneByRefParam = argListsWithOneByRefParamListener.Contexts.Select(context => new QualifiedContext(_qualifiedName, context)), |
| 93 | + }); |
| 94 | + } |
| 95 | + catch (COMException exception) |
| 96 | + { |
| 97 | + Debug.WriteLine("Exception thrown in thread {0}:\n{1}", Thread.CurrentThread.ManagedThreadId, exception); |
| 98 | + ParseFailure.Invoke(this, new ParseFailureArgs |
| 99 | + { |
| 100 | + Cause = exception |
| 101 | + }); |
| 102 | + } |
| 103 | + catch (SyntaxErrorException exception) |
| 104 | + { |
| 105 | + Debug.WriteLine("Exception thrown in thread {0}:\n{1}", Thread.CurrentThread.ManagedThreadId, exception); |
| 106 | + ParseFailure.Invoke(this, new ParseFailureArgs |
| 107 | + { |
| 108 | + Cause = exception |
| 109 | + }); |
| 110 | + } |
| 111 | + catch (OperationCanceledException cancel) |
| 112 | + { |
| 113 | + Debug.WriteLine("Operation was Cancelled", cancel); |
| 114 | + // no results to be used, so no results "returned" |
| 115 | + ParseCompleted.Invoke(this, new ParseCompletionArgs()); |
| 116 | + } |
| 117 | + } |
| 118 | + |
| 119 | + private string RewriteAndPreprocess() |
| 120 | + { |
| 121 | + var code = _rewriter == null ? string.Join(Environment.NewLine, _component.CodeModule.GetSanitizedCode()) : _rewriter.GetText(); |
| 122 | + string processed; |
| 123 | + try |
| 124 | + { |
| 125 | + processed = _preprocessor.Execute(code); |
| 126 | + } |
| 127 | + catch (VBAPreprocessorException) |
| 128 | + { |
| 129 | + Debug.WriteLine("Falling back to no preprocessing"); |
| 130 | + processed = code; |
| 131 | + } |
| 132 | + return processed; |
| 133 | + } |
| 134 | + |
| 135 | + private static IParseTree ParseInternal(string code, IEnumerable<IParseTreeListener> listeners, out ITokenStream outStream) |
| 136 | + { |
| 137 | + var stream = new AntlrInputStream(code); |
| 138 | + var lexer = new VBALexer(stream); |
| 139 | + var tokens = new CommonTokenStream(lexer); |
| 140 | + var parser = new VBAParser(tokens); |
| 141 | + |
| 142 | + parser.AddErrorListener(new ExceptionErrorListener()); |
| 143 | + foreach (var listener in listeners) |
| 144 | + { |
| 145 | + parser.AddParseListener(listener); |
| 146 | + } |
| 147 | + |
| 148 | + outStream = tokens; |
| 149 | + return parser.startRule(); |
| 150 | + } |
| 151 | + |
| 152 | + |
| 153 | + private IEnumerable<CommentNode> ParseComments(QualifiedModuleName qualifiedName, IEnumerable<VBAParser.CommentContext> comments, IEnumerable<VBAParser.RemCommentContext> remComments) |
| 154 | + { |
| 155 | + var commentNodes = comments.Select(comment => new CommentNode(comment.GetComment(), Tokens.CommentMarker, new QualifiedSelection(qualifiedName, comment.GetSelection()))); |
| 156 | + var remCommentNodes = remComments.Select(comment => new CommentNode(comment.GetComment(), Tokens.Rem, new QualifiedSelection(qualifiedName, comment.GetSelection()))); |
| 157 | + var allCommentNodes = commentNodes.Union(remCommentNodes); |
| 158 | + return allCommentNodes; |
| 159 | + } |
| 160 | + |
| 161 | + public void Parse() |
| 162 | + { |
| 163 | + ParseAsync(CancellationToken.None).Wait(); |
| 164 | + } |
| 165 | + |
| 166 | + public class ParseCompletionArgs |
| 167 | + { |
| 168 | + public ITokenStream Tokens { get; internal set; } |
| 169 | + public IParseTree ParseTree { get; internal set; } |
| 170 | + public IEnumerable<CommentNode> Comments { get; internal set; } |
| 171 | + public IEnumerable<QualifiedContext> ObsoleteCallContexts { get; internal set; } |
| 172 | + public IEnumerable<QualifiedContext> ObsoleteLetContexts { get; internal set; } |
| 173 | + public IEnumerable<QualifiedContext> EmptyStringLiterals { get; internal set; } |
| 174 | + public IEnumerable<QualifiedContext> ArgListsWithOneByRefParam { get; internal set; } |
| 175 | + public IEnumerable<Declaration> Declarations { get; internal set; } |
| 176 | + public IDictionary<Tuple<string, DeclarationType>, Attributes> Attributes { get; internal set; } |
| 177 | + } |
| 178 | + |
| 179 | + public class ParseFailureArgs |
| 180 | + { |
| 181 | + public Exception Cause { get; internal set; } |
| 182 | + } |
| 183 | + } |
| 184 | + |
| 185 | + #region Listener classes |
| 186 | + class ObsoleteCallStatementListener : VBABaseListener |
| 187 | + { |
| 188 | + private readonly IList<VBAParser.ExplicitCallStmtContext> _contexts = new List<VBAParser.ExplicitCallStmtContext>(); |
| 189 | + public IEnumerable<VBAParser.ExplicitCallStmtContext> Contexts { get { return _contexts; } } |
| 190 | + |
| 191 | + public override void ExitExplicitCallStmt(VBAParser.ExplicitCallStmtContext context) |
| 192 | + { |
| 193 | + var procedureCall = context.eCS_ProcedureCall(); |
| 194 | + if (procedureCall != null) |
| 195 | + { |
| 196 | + if (procedureCall.CALL() != null) |
| 197 | + { |
| 198 | + _contexts.Add(context); |
| 199 | + return; |
| 200 | + } |
| 201 | + } |
| 202 | + |
| 203 | + var memberCall = context.eCS_MemberProcedureCall(); |
| 204 | + if (memberCall == null) return; |
| 205 | + if (memberCall.CALL() == null) return; |
| 206 | + _contexts.Add(context); |
| 207 | + } |
| 208 | + } |
| 209 | + |
| 210 | + class ObsoleteLetStatementListener : VBABaseListener |
| 211 | + { |
| 212 | + private readonly IList<VBAParser.LetStmtContext> _contexts = new List<VBAParser.LetStmtContext>(); |
| 213 | + public IEnumerable<VBAParser.LetStmtContext> Contexts { get { return _contexts; } } |
| 214 | + |
| 215 | + public override void ExitLetStmt(VBAParser.LetStmtContext context) |
| 216 | + { |
| 217 | + if (context.LET() != null) |
| 218 | + { |
| 219 | + _contexts.Add(context); |
| 220 | + } |
| 221 | + } |
| 222 | + } |
| 223 | + |
| 224 | + class EmptyStringLiteralListener : VBABaseListener |
| 225 | + { |
| 226 | + private readonly IList<VBAParser.LiteralContext> _contexts = new List<VBAParser.LiteralContext>(); |
| 227 | + public IEnumerable<VBAParser.LiteralContext> Contexts { get { return _contexts; } } |
| 228 | + |
| 229 | + public override void ExitLiteral(VBAParser.LiteralContext context) |
| 230 | + { |
| 231 | + var literal = context.STRINGLITERAL(); |
| 232 | + if (literal != null && literal.GetText() == "\"\"") |
| 233 | + { |
| 234 | + _contexts.Add(context); |
| 235 | + } |
| 236 | + } |
| 237 | + } |
| 238 | + |
| 239 | + class ArgListWithOneByRefParamListener : VBABaseListener |
| 240 | + { |
| 241 | + private readonly IList<VBAParser.ArgListContext> _contexts = new List<VBAParser.ArgListContext>(); |
| 242 | + public IEnumerable<VBAParser.ArgListContext> Contexts { get { return _contexts; } } |
| 243 | + |
| 244 | + public override void ExitArgList(VBAParser.ArgListContext context) |
| 245 | + { |
| 246 | + if (context.arg() != null && context.arg().Count(a => a.BYREF() != null || (a.BYREF() == null && a.BYVAL() == null)) == 1) |
| 247 | + { |
| 248 | + _contexts.Add(context); |
| 249 | + } |
| 250 | + } |
| 251 | + } |
| 252 | + |
| 253 | + class CommentListener : VBABaseListener |
| 254 | + { |
| 255 | + private readonly IList<VBAParser.RemCommentContext> _remComments = new List<VBAParser.RemCommentContext>(); |
| 256 | + public IEnumerable<VBAParser.RemCommentContext> RemComments { get { return _remComments; } } |
| 257 | + |
| 258 | + private readonly IList<VBAParser.CommentContext> _comments = new List<VBAParser.CommentContext>(); |
| 259 | + public IEnumerable<VBAParser.CommentContext> Comments { get { return _comments; } } |
| 260 | + |
| 261 | + public override void ExitRemComment([NotNull] VBAParser.RemCommentContext context) |
| 262 | + { |
| 263 | + _remComments.Add(context); |
| 264 | + } |
| 265 | + |
| 266 | + public override void ExitComment([NotNull] VBAParser.CommentContext context) |
| 267 | + { |
| 268 | + _comments.Add(context); |
| 269 | + } |
| 270 | + } |
| 271 | + |
| 272 | + #endregion |
| 273 | +} |
0 commit comments