Skip to content

Commit dd8f43e

Browse files
Andrin Meierretailcoder
authored andcommitted
replace event handling meachnism in declaration listener with a simple list + fix duplicate "declaration created" events (#1638)
1 parent db9c758 commit dd8f43e

File tree

3 files changed

+49
-62
lines changed

3 files changed

+49
-62
lines changed

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
using Rubberduck.VBEditor;
55
using System;
66
using System.Collections.Generic;
7-
using System.Diagnostics;
87
using System.Linq;
98

109
namespace Rubberduck.Parsing.Symbols

Rubberduck.Parsing/Symbols/DeclarationSymbolsListener.cs

Lines changed: 43 additions & 55 deletions
Original file line numberDiff line numberDiff line change
@@ -27,9 +27,11 @@ public class DeclarationSymbolsListener : VBAParserBaseListener
2727
private readonly IDictionary<Tuple<string, DeclarationType>, Attributes> _attributes;
2828
private readonly HashSet<ReferencePriorityMap> _projectReferences;
2929

30+
private readonly List<Declaration> _createdDeclarations = new List<Declaration>();
31+
public IReadOnlyList<Declaration> CreatedDeclarations { get { return _createdDeclarations; } }
32+
3033
public DeclarationSymbolsListener(
3134
QualifiedModuleName qualifiedName,
32-
Accessibility componentAccessibility,
3335
vbext_ComponentType type,
3436
IEnumerable<CommentNode> comments,
3537
IEnumerable<IAnnotation> annotations,
@@ -76,8 +78,13 @@ public DeclarationSymbolsListener(
7678
moduleAttributes,
7779
hasDefaultInstanceVariable: hasDefaultInstanceVariable);
7880
}
79-
8081
SetCurrentScope();
82+
AddDeclaration(_moduleDeclaration);
83+
var component = _moduleDeclaration.QualifiedName.QualifiedModuleName.Component;
84+
if (component.Type == vbext_ComponentType.vbext_ct_MSForm || component.Designer != null)
85+
{
86+
DeclareControlsAsMembers(component);
87+
}
8188
}
8289

8390
private IEnumerable<IAnnotation> FindAnnotations()
@@ -117,27 +124,6 @@ private IEnumerable<IAnnotation> FindAnnotations(int line)
117124
return annotations;
118125
}
119126

120-
public void CreateModuleDeclarations()
121-
{
122-
OnNewDeclaration(_moduleDeclaration);
123-
124-
var component = _moduleDeclaration.QualifiedName.QualifiedModuleName.Component;
125-
if (component.Type == vbext_ComponentType.vbext_ct_MSForm || component.Designer != null)
126-
{
127-
DeclareControlsAsMembers(component);
128-
}
129-
}
130-
131-
public event EventHandler<DeclarationEventArgs> NewDeclaration;
132-
private void OnNewDeclaration(Declaration declaration)
133-
{
134-
var handler = NewDeclaration;
135-
if (handler != null)
136-
{
137-
handler.Invoke(this, new DeclarationEventArgs(declaration));
138-
}
139-
}
140-
141127
/// <summary>
142128
/// Scans form designer to create a public, self-assigned field for each control on a form.
143129
/// </summary>
@@ -177,7 +163,7 @@ private void DeclareControlsAsMembers(VBComponent form)
177163
false,
178164
null,
179165
false);
180-
OnNewDeclaration(declaration);
166+
AddDeclaration(declaration);
181167
}
182168
}
183169

@@ -303,7 +289,6 @@ private Declaration CreateDeclaration(
303289
((ClassModuleDeclaration)_parentDeclaration).DefaultMember = result;
304290
}
305291
}
306-
OnNewDeclaration(result);
307292
return result;
308293
}
309294

@@ -361,7 +346,7 @@ public override void EnterImplementsStmt(VBAParser.ImplementsStmtContext context
361346

362347
public override void EnterOptionBaseStmt(VBAParser.OptionBaseStmtContext context)
363348
{
364-
OnNewDeclaration(CreateDeclaration(
349+
AddDeclaration(CreateDeclaration(
365350
context.GetText(),
366351
string.Empty,
367352
Accessibility.Implicit,
@@ -375,7 +360,7 @@ public override void EnterOptionBaseStmt(VBAParser.OptionBaseStmtContext context
375360

376361
public override void EnterOptionCompareStmt(VBAParser.OptionCompareStmtContext context)
377362
{
378-
OnNewDeclaration(CreateDeclaration(
363+
AddDeclaration(CreateDeclaration(
379364
context.GetText(),
380365
string.Empty,
381366
Accessibility.Implicit,
@@ -389,7 +374,7 @@ public override void EnterOptionCompareStmt(VBAParser.OptionCompareStmtContext c
389374

390375
public override void EnterOptionExplicitStmt(VBAParser.OptionExplicitStmtContext context)
391376
{
392-
OnNewDeclaration(CreateDeclaration(
377+
AddDeclaration(CreateDeclaration(
393378
context.GetText(),
394379
string.Empty,
395380
Accessibility.Implicit,
@@ -407,7 +392,7 @@ public override void ExitOptionPrivateModuleStmt(VBAParser.OptionPrivateModuleSt
407392
{
408393
((ProceduralModuleDeclaration)_moduleDeclaration).IsPrivateModule = true;
409394
}
410-
OnNewDeclaration(
395+
AddDeclaration(
411396
CreateDeclaration(
412397
context.GetText(),
413398
string.Empty,
@@ -439,7 +424,7 @@ public override void EnterSubStmt(VBAParser.SubStmtContext context)
439424
false,
440425
null,
441426
null);
442-
OnNewDeclaration(declaration);
427+
AddDeclaration(declaration);
443428
SetCurrentScope(declaration, name);
444429
}
445430

@@ -474,7 +459,7 @@ public override void EnterFunctionStmt(VBAParser.FunctionStmtContext context)
474459
isArray,
475460
asTypeClause,
476461
typeHint);
477-
OnNewDeclaration(declaration);
462+
AddDeclaration(declaration);
478463
SetCurrentScope(declaration, name);
479464
}
480465

@@ -505,7 +490,7 @@ public override void EnterPropertyGetStmt(VBAParser.PropertyGetStmtContext conte
505490
asTypeClause,
506491
typeHint);
507492

508-
OnNewDeclaration(declaration);
493+
AddDeclaration(declaration);
509494
SetCurrentScope(declaration, name);
510495
}
511496

@@ -533,7 +518,7 @@ public override void EnterPropertyLetStmt(VBAParser.PropertyLetStmtContext conte
533518
false,
534519
null,
535520
null);
536-
OnNewDeclaration(declaration);
521+
AddDeclaration(declaration);
537522
SetCurrentScope(declaration, name);
538523
}
539524

@@ -563,7 +548,7 @@ public override void EnterPropertySetStmt(VBAParser.PropertySetStmtContext conte
563548
null,
564549
null);
565550

566-
OnNewDeclaration(declaration);
551+
AddDeclaration(declaration);
567552
SetCurrentScope(declaration, name);
568553
}
569554

@@ -593,7 +578,7 @@ public override void EnterEventStmt(VBAParser.EventStmtContext context)
593578
null,
594579
null);
595580

596-
OnNewDeclaration(declaration);
581+
AddDeclaration(declaration);
597582
SetCurrentScope(declaration, name);
598583
}
599584

@@ -638,7 +623,7 @@ public override void EnterDeclareStmt(VBAParser.DeclareStmtContext context)
638623
asTypeClause,
639624
typeHint);
640625

641-
OnNewDeclaration(declaration);
626+
AddDeclaration(declaration);
642627
SetCurrentScope(declaration, name); // treat like a procedure block, to correctly scope parameters.
643628
}
644629

@@ -659,7 +644,7 @@ public override void EnterArgList(VBAParser.ArgListContext context)
659644
var identifier = argContext.unrestrictedIdentifier();
660645
string typeHint = Identifier.GetTypeHintValue(identifier);
661646
bool isArray = argContext.LPAREN() != null;
662-
OnNewDeclaration(
647+
AddDeclaration(
663648
CreateDeclaration(
664649
Identifier.GetName(identifier),
665650
asTypeName,
@@ -675,7 +660,7 @@ public override void EnterArgList(VBAParser.ArgListContext context)
675660

676661
public override void EnterStatementLabelDefinition(VBAParser.StatementLabelDefinitionContext context)
677662
{
678-
OnNewDeclaration(
663+
AddDeclaration(
679664
CreateDeclaration(
680665
context.statementLabel().GetText(),
681666
null,
@@ -706,7 +691,7 @@ public override void EnterVariableSubStmt(VBAParser.VariableSubStmtContext conte
706691
var withEvents = parent.WITHEVENTS() != null;
707692
var isAutoObject = asTypeClause != null && asTypeClause.NEW() != null;
708693
bool isArray = context.LPAREN() != null;
709-
OnNewDeclaration(
694+
AddDeclaration(
710695
CreateDeclaration(
711696
name,
712697
asTypeName,
@@ -747,7 +732,7 @@ public override void EnterConstSubStmt(VBAParser.ConstSubStmtContext context)
747732
context,
748733
identifier.GetSelection());
749734

750-
OnNewDeclaration(declaration);
735+
AddDeclaration(declaration);
751736
}
752737

753738
public override void EnterTypeStmt(VBAParser.TypeStmtContext context)
@@ -769,7 +754,7 @@ public override void EnterTypeStmt(VBAParser.TypeStmtContext context)
769754
null,
770755
null);
771756

772-
OnNewDeclaration(declaration);
757+
AddDeclaration(declaration);
773758
_parentDeclaration = declaration; // treat members as child declarations, but keep them scoped to module
774759
}
775760

@@ -786,7 +771,7 @@ public override void EnterTypeStmt_Element(VBAParser.TypeStmt_ElementContext con
786771
: asTypeClause.type().GetText();
787772
bool isArray = context.LPAREN() != null;
788773
string typeHint = Identifier.GetTypeHintValue(context.identifier());
789-
OnNewDeclaration(
774+
AddDeclaration(
790775
CreateDeclaration(
791776
context.identifier().GetText(),
792777
asTypeName,
@@ -820,7 +805,7 @@ public override void EnterEnumerationStmt(VBAParser.EnumerationStmtContext conte
820805
null,
821806
null);
822807

823-
OnNewDeclaration(declaration);
808+
AddDeclaration(declaration);
824809
_parentDeclaration = declaration; // treat members as child declarations, but keep them scoped to module
825810
}
826811

@@ -830,19 +815,22 @@ public override void ExitEnumerationStmt(VBAParser.EnumerationStmtContext contex
830815
}
831816

832817
public override void EnterEnumerationStmt_Constant(VBAParser.EnumerationStmt_ConstantContext context)
833-
{
818+
{
819+
AddDeclaration(CreateDeclaration(
820+
context.identifier().GetText(),
821+
"Long",
822+
Accessibility.Implicit,
823+
DeclarationType.EnumerationMember,
824+
context,
825+
context.identifier().GetSelection(),
826+
false,
827+
null,
828+
null));
829+
}
834830

835-
OnNewDeclaration(
836-
CreateDeclaration(
837-
context.identifier().GetText(),
838-
"Long",
839-
Accessibility.Implicit,
840-
DeclarationType.EnumerationMember,
841-
context,
842-
context.identifier().GetSelection(),
843-
false,
844-
null,
845-
null));
831+
private void AddDeclaration(Declaration declaration)
832+
{
833+
_createdDeclarations.Add(declaration);
846834
}
847835
}
848836
}

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -538,13 +538,13 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
538538
_state.AddDeclaration(projectDeclaration);
539539
}
540540
}
541-
var declarationsListener = new DeclarationSymbolsListener(qualifiedModuleName, Accessibility.Implicit, component.Type, _state.GetModuleComments(component), _state.GetModuleAnnotations(component), _state.GetModuleAttributes(component), _projectReferences, projectDeclaration);
542-
// TODO: should we unify the API? consider working like the other listeners instead of event-based
543-
declarationsListener.NewDeclaration += (sender, e) => _state.AddDeclaration(e.Declaration);
544-
declarationsListener.CreateModuleDeclarations();
545-
546-
_logger.Debug("Walking parse tree for '{0}'... (acquiring declarations)", qualifiedModuleName.Name);
541+
_logger.Debug("Creating declarations for module {0}.", qualifiedModuleName.Name);
542+
var declarationsListener = new DeclarationSymbolsListener(qualifiedModuleName, component.Type, _state.GetModuleComments(component), _state.GetModuleAnnotations(component), _state.GetModuleAttributes(component), _projectReferences, projectDeclaration);
547543
ParseTreeWalker.Default.Walk(declarationsListener, tree);
544+
foreach (var createdDeclaration in declarationsListener.CreatedDeclarations)
545+
{
546+
_state.AddDeclaration(createdDeclaration);
547+
}
548548
}
549549
catch (Exception exception)
550550
{

0 commit comments

Comments
 (0)