Skip to content

Commit 0ac73b8

Browse files
committed
Inline IdentifierAnnotationService
The only method does no longer contain a lot of logic; it is just one call to the `DeclarationFinder` followed by a single `Where` on the annotation type.
1 parent 5356895 commit 0ac73b8

File tree

4 files changed

+33
-42
lines changed

4 files changed

+33
-42
lines changed

Rubberduck.Parsing/Annotations/IdentifierAnnotationService.cs

Lines changed: 0 additions & 22 deletions
This file was deleted.

Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,6 @@ public sealed class IdentifierReferenceResolver
2323
private Declaration _currentParent;
2424
private readonly BindingService _bindingService;
2525
private readonly BoundExpressionVisitor _boundExpressionVisitor;
26-
private readonly IdentifierAnnotationService _identifierAnnotationService;
2726
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
2827

2928
public IdentifierReferenceResolver(QualifiedModuleName qualifiedModuleName, DeclarationFinder finder)
@@ -44,8 +43,7 @@ public IdentifierReferenceResolver(QualifiedModuleName qualifiedModuleName, Decl
4443
new DefaultBindingContext(_declarationFinder, typeBindingContext, procedurePointerBindingContext),
4544
typeBindingContext,
4645
procedurePointerBindingContext);
47-
_identifierAnnotationService = new IdentifierAnnotationService(_declarationFinder);
48-
_boundExpressionVisitor = new BoundExpressionVisitor(_identifierAnnotationService);
46+
_boundExpressionVisitor = new BoundExpressionVisitor(finder);
4947
}
5048

5149
public void SetCurrentScope()
@@ -153,10 +151,16 @@ private void ResolveLabel(ParserRuleContext context, string label)
153151
identifier,
154152
callee,
155153
callSiteContext.GetSelection(),
156-
_identifierAnnotationService.FindAnnotations(_qualifiedModuleName, callSiteContext.GetSelection().StartLine));
154+
FindIdentifierAnnotations(_qualifiedModuleName, callSiteContext.GetSelection().StartLine));
157155
}
158156
}
159157

158+
private IEnumerable<IAnnotation> FindIdentifierAnnotations(QualifiedModuleName module, int line)
159+
{
160+
return _declarationFinder.FindAnnotations(module, line)
161+
.Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation));
162+
}
163+
160164
private void ResolveDefault(
161165
ParserRuleContext expression,
162166
StatementResolutionContext statementContext = StatementResolutionContext.Undefined,
@@ -713,7 +717,7 @@ public void Resolve(VBAParser.RaiseEventStmtContext context)
713717
identifier,
714718
callee,
715719
callSiteContext.GetSelection(),
716-
_identifierAnnotationService.FindAnnotations(_qualifiedModuleName, callSiteContext.GetSelection().StartLine));
720+
FindIdentifierAnnotations(_qualifiedModuleName, callSiteContext.GetSelection().StartLine));
717721
}
718722
if (context.eventArgumentList() == null)
719723
{
@@ -819,7 +823,7 @@ public void Resolve(VBAParser.DebugPrintStmtContext context)
819823
context.debugPrint().debugModule().GetText(),
820824
debugModule,
821825
context.debugPrint().debugModule().GetSelection(),
822-
_identifierAnnotationService.FindAnnotations(_qualifiedModuleName, context.debugPrint().debugModule().GetSelection().StartLine));
826+
FindIdentifierAnnotations(_qualifiedModuleName, context.debugPrint().debugModule().GetSelection().StartLine));
823827
debugPrint.AddReference(
824828
_qualifiedModuleName,
825829
_currentScope,
@@ -828,7 +832,7 @@ public void Resolve(VBAParser.DebugPrintStmtContext context)
828832
context.debugPrint().debugPrintSub().GetText(),
829833
debugPrint,
830834
context.debugPrint().debugPrintSub().GetSelection(),
831-
_identifierAnnotationService.FindAnnotations(_qualifiedModuleName, context.debugPrint().debugPrintSub().GetSelection().StartLine));
835+
FindIdentifierAnnotations(_qualifiedModuleName, context.debugPrint().debugPrintSub().GetSelection().StartLine));
832836
var outputList = context.outputList();
833837
if (outputList != null)
834838
{

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,6 @@ public class DeclarationFinder
2222
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
2323

2424
private readonly IHostApplication _hostApp;
25-
private readonly IdentifierAnnotationService _identifierAnnotationService;
2625
private IDictionary<string, List<Declaration>> _declarationsByName;
2726
private IDictionary<QualifiedModuleName, List<Declaration>> _declarations;
2827
private readonly ConcurrentDictionary<QualifiedMemberName, ConcurrentBag<Declaration>> _newUndeclared;
@@ -68,8 +67,6 @@ public DeclarationFinder(IReadOnlyList<Declaration> declarations, IEnumerable<IA
6867
_newUndeclared = new ConcurrentDictionary<QualifiedMemberName, ConcurrentBag<Declaration>>(new Dictionary<QualifiedMemberName, ConcurrentBag<Declaration>>());
6968
_newUnresolved = new ConcurrentBag<UnboundMemberDeclaration>(new List<UnboundMemberDeclaration>());
7069

71-
_identifierAnnotationService = new IdentifierAnnotationService(this);
72-
7370
var collectionConstructionActions = CollectionConstructionActions(declarations, annotations, unresolvedMemberDeclarations);
7471
ExecuteCollectionConstructionActions(collectionConstructionActions);
7572

@@ -815,7 +812,8 @@ public Declaration FindMemberEnclosingProcedure(Declaration enclosingProcedure,
815812

816813
public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string identifierName, ParserRuleContext context)
817814
{
818-
var annotations = _identifierAnnotationService.FindAnnotations(enclosingProcedure.QualifiedName.QualifiedModuleName, context.Start.Line);
815+
var annotations = FindAnnotations(enclosingProcedure.QualifiedName.QualifiedModuleName, context.Start.Line)
816+
.Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation));
819817
var undeclaredLocal =
820818
new Declaration(
821819
new QualifiedMemberName(enclosingProcedure.QualifiedName.QualifiedModuleName, identifierName),
@@ -870,7 +868,8 @@ public void AddUnboundContext(Declaration parentDeclaration, VBAParser.LExpressi
870868
}
871869

872870
var identifier = context.GetChild<VBAParser.UnrestrictedIdentifierContext>(0);
873-
var annotations = _identifierAnnotationService.FindAnnotations(parentDeclaration.QualifiedName.QualifiedModuleName, context.Start.Line);
871+
var annotations = FindAnnotations(parentDeclaration.QualifiedName.QualifiedModuleName, context.Start.Line)
872+
.Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation));
874873

875874
var declaration = new UnboundMemberDeclaration(parentDeclaration, identifier,
876875
(context is VBAParser.MemberAccessExprContext) ? (ParserRuleContext)context.children[0] : withExpression.Context,

Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs

Lines changed: 18 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,11 @@
1-
using Rubberduck.Parsing.Annotations;
1+
using System.Collections;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using Rubberduck.Parsing.Annotations;
25
using Rubberduck.Parsing.Binding;
36
using Rubberduck.Parsing.Grammar;
47
using Rubberduck.Parsing.Symbols;
8+
using Rubberduck.Parsing.VBA.DeclarationCaching;
59
using Rubberduck.VBEditor;
610

711
// ReSharper disable UnusedParameter.Local - calls are dynamic, so the signatures need to match.
@@ -10,11 +14,11 @@ namespace Rubberduck.Parsing.VBA.ReferenceManagement
1014
{
1115
public sealed class BoundExpressionVisitor
1216
{
13-
private readonly IdentifierAnnotationService _identifierAnnotationService;
17+
private readonly DeclarationFinder _declarationFinder;
1418

15-
public BoundExpressionVisitor(IdentifierAnnotationService identifierAnnotationService)
19+
public BoundExpressionVisitor(DeclarationFinder declarationFinder)
1620
{
17-
_identifierAnnotationService = identifierAnnotationService;
21+
_declarationFinder = declarationFinder;
1822
}
1923

2024
public void AddIdentifierReferences(
@@ -73,12 +77,18 @@ private void Visit(
7377
identifier,
7478
callee,
7579
callSiteContext.GetSelection(),
76-
_identifierAnnotationService.FindAnnotations(module, callSiteContext.GetSelection().StartLine),
80+
FindIdentifierAnnotations(module, callSiteContext.GetSelection().StartLine),
7781
isAssignmentTarget,
7882
hasExplicitLetStatement,
7983
isSetAssignment);
8084
}
8185

86+
private IEnumerable<IAnnotation> FindIdentifierAnnotations(QualifiedModuleName module, int line)
87+
{
88+
return _declarationFinder.FindAnnotations(module, line)
89+
.Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation));
90+
}
91+
8292
private void Visit(
8393
MemberAccessExpression expression,
8494
QualifiedModuleName module,
@@ -103,7 +113,7 @@ private void Visit(
103113
identifier,
104114
callee,
105115
callSiteContext.GetSelection(),
106-
_identifierAnnotationService.FindAnnotations(module, callSiteContext.GetSelection().StartLine),
116+
FindIdentifierAnnotations(module, callSiteContext.GetSelection().StartLine),
107117
isAssignmentTarget,
108118
hasExplicitLetStatement,
109119
isSetAssignment);
@@ -140,7 +150,7 @@ private void Visit(
140150
identifier,
141151
callee,
142152
callSiteContext.GetSelection(),
143-
_identifierAnnotationService.FindAnnotations(module, callSiteContext.GetSelection().StartLine),
153+
FindIdentifierAnnotations(module, callSiteContext.GetSelection().StartLine),
144154
isSetAssignment);
145155
}
146156
}
@@ -254,7 +264,7 @@ private void Visit(
254264
identifier,
255265
callee,
256266
callSiteContext.GetSelection(),
257-
_identifierAnnotationService.FindAnnotations(module, callSiteContext.GetSelection().StartLine),
267+
FindIdentifierAnnotations(module, callSiteContext.GetSelection().StartLine),
258268
isAssignmentTarget,
259269
hasExplicitLetStatement,
260270
isSetAssignment);

0 commit comments

Comments
 (0)