Skip to content

Commit ac6b85d

Browse files
committed
added caching to avoid exporting / parsing attributes *every time* a module is parsed.
1 parent 63bef89 commit ac6b85d

File tree

2 files changed

+25
-5
lines changed

2 files changed

+25
-5
lines changed

Rubberduck.Parsing/Symbols/DeclarationSymbolsListener.cs

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -154,8 +154,15 @@ private Declaration CreateDeclaration(string identifierName, string asTypeName,
154154
}
155155
else
156156
{
157+
var key = Tuple.Create(identifierName, declarationType);
158+
Attributes attributes = null;
159+
if (_attributes.ContainsKey(key))
160+
{
161+
attributes = _attributes[key];
162+
}
163+
157164
var annotations = FindAnnotations(selection.StartLine);
158-
result = new Declaration(new QualifiedMemberName(_qualifiedName, identifierName), _parentDeclaration, _currentScopeDeclaration, asTypeName, selfAssigned, withEvents, accessibility, declarationType, context, selection, false, annotations);
165+
result = new Declaration(new QualifiedMemberName(_qualifiedName, identifierName), _parentDeclaration, _currentScopeDeclaration, asTypeName, selfAssigned, withEvents, accessibility, declarationType, context, selection, false, annotations, attributes);
159166
}
160167

161168
OnNewDeclaration(result);

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 17 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -97,6 +97,12 @@ private void ParseInternal()
9797
.SelectMany(project => project.VBComponents.Cast<VBComponent>())
9898
.ToList();
9999

100+
var invalidCache = _componentAttributes.Keys.Except(components).ToList();
101+
foreach (var component in invalidCache)
102+
{
103+
_componentAttributes.Remove(component);
104+
}
105+
100106
foreach (var vbComponent in components)
101107
{
102108
while (!_state.ClearDeclarations(vbComponent))
@@ -147,8 +153,6 @@ public void ParseComponent(VBComponent vbComponent, TokenStreamRewriter rewriter
147153

148154
try
149155
{
150-
var attributes = _attributeParser.Parse(component);
151-
152156
var qualifiedName = new QualifiedModuleName(vbComponent);
153157
var code = rewriter == null ? string.Join(Environment.NewLine, vbComponent.CodeModule.GetSanitizedCode()) : rewriter.GetText();
154158

@@ -180,7 +184,7 @@ public void ParseComponent(VBComponent vbComponent, TokenStreamRewriter rewriter
180184
};
181185

182186
var tree = GetParseTree(vbComponent, listeners, preprocessedModuleBody, qualifiedName);
183-
WalkParseTree(vbComponent, listeners, qualifiedName, tree, attributes);
187+
WalkParseTree(vbComponent, listeners, qualifiedName, tree);
184188

185189
State.SetModuleState(vbComponent, ParserState.Parsed);
186190
}
@@ -222,13 +226,22 @@ private IParseTree GetParseTree(VBComponent vbComponent, IParseTreeListener[] li
222226
return tree;
223227
}
224228

225-
private void WalkParseTree(VBComponent vbComponent, IReadOnlyList<IParseTreeListener> listeners, QualifiedModuleName qualifiedName, IParseTree tree, IDictionary<Tuple<string, DeclarationType>, Attributes> attributes)
229+
private readonly IDictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>> _componentAttributes
230+
= new Dictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>>();
231+
232+
private void WalkParseTree(VBComponent vbComponent, IReadOnlyList<IParseTreeListener> listeners, QualifiedModuleName qualifiedName, IParseTree tree)
226233
{
227234
var obsoleteCallsListener = listeners.OfType<ObsoleteCallStatementListener>().Single();
228235
var obsoleteLetListener = listeners.OfType<ObsoleteLetStatementListener>().Single();
229236
var emptyStringLiteralListener = listeners.OfType<EmptyStringLiteralListener>().Single();
230237
var argListsWithOneByRefParamListener = listeners.OfType<ArgListWithOneByRefParamListener>().Single();
231238

239+
if (!_componentAttributes.ContainsKey(vbComponent))
240+
{
241+
_componentAttributes.Add(vbComponent, _attributeParser.Parse(vbComponent));
242+
}
243+
var attributes = _componentAttributes[vbComponent];
244+
232245
// cannot locate declarations in one pass *the way it's currently implemented*,
233246
// because the context in EnterSubStmt() doesn't *yet* have child nodes when the context enters.
234247
// so we need to EnterAmbiguousIdentifier() and evaluate the parent instead - this *might* work.

0 commit comments

Comments
 (0)