Skip to content

Commit 8c5f900

Browse files
committed
Make tests pass for new annotation scoping design
Annotations only get scoped to recipients now for which they have a corresponding flag.
1 parent 2ba2ef8 commit 8c5f900

File tree

7 files changed

+77
-81
lines changed

7 files changed

+77
-81
lines changed

Rubberduck.Parsing/Annotations/AnnotationService.cs renamed to Rubberduck.Parsing/Annotations/IdentifierAnnotationService.cs

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,16 +1,15 @@
1-
using Rubberduck.Parsing.Symbols;
2-
using Rubberduck.VBEditor;
1+
using Rubberduck.VBEditor;
32
using System.Collections.Generic;
43
using System.Linq;
54
using Rubberduck.Parsing.VBA.DeclarationCaching;
65

76
namespace Rubberduck.Parsing.Annotations
87
{
9-
public sealed class AnnotationService
8+
public sealed class IdentifierAnnotationService
109
{
1110
private readonly DeclarationFinder _declarationFinder;
1211

13-
public AnnotationService(DeclarationFinder declarationFinder)
12+
public IdentifierAnnotationService(DeclarationFinder declarationFinder)
1413
{
1514
_declarationFinder = declarationFinder;
1615
}
@@ -22,13 +21,15 @@ public IEnumerable<IAnnotation> FindAnnotations(QualifiedModuleName module, int
2221
// VBE 1-based indexing
2322
for (var currentLine = line - 1; currentLine >= 1; currentLine--)
2423
{
24+
//Identifier annotation sections end at the first line above without an identifier annotation.
2525
if (!moduleAnnotations.Any(annotation => annotation.QualifiedSelection.Selection.StartLine <= currentLine
26-
&& annotation.QualifiedSelection.Selection.EndLine >= currentLine))
26+
&& annotation.QualifiedSelection.Selection.EndLine >= currentLine
27+
&& annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation)))
2728
{
2829
break;
2930
}
3031

31-
var annotationsStartingOnCurrentLine = moduleAnnotations.Where(a => a.QualifiedSelection.Selection.StartLine == currentLine);
32+
var annotationsStartingOnCurrentLine = moduleAnnotations.Where(a => a.QualifiedSelection.Selection.StartLine == currentLine && a.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation));
3233

3334
annotations.AddRange(annotationsStartingOnCurrentLine);
3435
}

Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs

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

2929
public IdentifierReferenceResolver(QualifiedModuleName qualifiedModuleName, DeclarationFinder finder)
@@ -44,8 +44,8 @@ public IdentifierReferenceResolver(QualifiedModuleName qualifiedModuleName, Decl
4444
new DefaultBindingContext(_declarationFinder, typeBindingContext, procedurePointerBindingContext),
4545
typeBindingContext,
4646
procedurePointerBindingContext);
47-
_annotationService = new AnnotationService(_declarationFinder);
48-
_boundExpressionVisitor = new BoundExpressionVisitor(_annotationService);
47+
_identifierAnnotationService = new IdentifierAnnotationService(_declarationFinder);
48+
_boundExpressionVisitor = new BoundExpressionVisitor(_identifierAnnotationService);
4949
}
5050

5151
public void SetCurrentScope()
@@ -153,7 +153,7 @@ private void ResolveLabel(ParserRuleContext context, string label)
153153
identifier,
154154
callee,
155155
callSiteContext.GetSelection(),
156-
_annotationService.FindAnnotations(_qualifiedModuleName, callSiteContext.GetSelection().StartLine));
156+
_identifierAnnotationService.FindAnnotations(_qualifiedModuleName, callSiteContext.GetSelection().StartLine));
157157
}
158158
}
159159

@@ -713,7 +713,7 @@ public void Resolve(VBAParser.RaiseEventStmtContext context)
713713
identifier,
714714
callee,
715715
callSiteContext.GetSelection(),
716-
_annotationService.FindAnnotations(_qualifiedModuleName, callSiteContext.GetSelection().StartLine));
716+
_identifierAnnotationService.FindAnnotations(_qualifiedModuleName, callSiteContext.GetSelection().StartLine));
717717
}
718718
if (context.eventArgumentList() == null)
719719
{
@@ -819,7 +819,7 @@ public void Resolve(VBAParser.DebugPrintStmtContext context)
819819
context.debugPrint().debugModule().GetText(),
820820
debugModule,
821821
context.debugPrint().debugModule().GetSelection(),
822-
_annotationService.FindAnnotations(_qualifiedModuleName, context.debugPrint().debugModule().GetSelection().StartLine));
822+
_identifierAnnotationService.FindAnnotations(_qualifiedModuleName, context.debugPrint().debugModule().GetSelection().StartLine));
823823
debugPrint.AddReference(
824824
_qualifiedModuleName,
825825
_currentScope,
@@ -828,7 +828,7 @@ public void Resolve(VBAParser.DebugPrintStmtContext context)
828828
context.debugPrint().debugPrintSub().GetText(),
829829
debugPrint,
830830
context.debugPrint().debugPrintSub().GetSelection(),
831-
_annotationService.FindAnnotations(_qualifiedModuleName, context.debugPrint().debugPrintSub().GetSelection().StartLine));
831+
_identifierAnnotationService.FindAnnotations(_qualifiedModuleName, context.debugPrint().debugPrintSub().GetSelection().StartLine));
832832
var outputList = context.outputList();
833833
if (outputList != null)
834834
{

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

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

2424
private readonly IHostApplication _hostApp;
25-
private readonly AnnotationService _annotationService;
25+
private readonly IdentifierAnnotationService _identifierAnnotationService;
2626
private IDictionary<string, List<Declaration>> _declarationsByName;
2727
private IDictionary<QualifiedModuleName, List<Declaration>> _declarations;
2828
private readonly ConcurrentDictionary<QualifiedMemberName, ConcurrentBag<Declaration>> _newUndeclared;
@@ -68,7 +68,7 @@ public DeclarationFinder(IReadOnlyList<Declaration> declarations, IEnumerable<IA
6868
_newUndeclared = new ConcurrentDictionary<QualifiedMemberName, ConcurrentBag<Declaration>>(new Dictionary<QualifiedMemberName, ConcurrentBag<Declaration>>());
6969
_newUnresolved = new ConcurrentBag<UnboundMemberDeclaration>(new List<UnboundMemberDeclaration>());
7070

71-
_annotationService = new AnnotationService(this);
71+
_identifierAnnotationService = new IdentifierAnnotationService(this);
7272

7373
var collectionConstructionActions = CollectionConstructionActions(declarations, annotations, unresolvedMemberDeclarations);
7474
ExecuteCollectionConstructionActions(collectionConstructionActions);
@@ -804,7 +804,7 @@ public Declaration FindMemberEnclosingProcedure(Declaration enclosingProcedure,
804804

805805
public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string identifierName, ParserRuleContext context)
806806
{
807-
var annotations = _annotationService.FindAnnotations(enclosingProcedure.QualifiedName.QualifiedModuleName, context.Start.Line);
807+
var annotations = _identifierAnnotationService.FindAnnotations(enclosingProcedure.QualifiedName.QualifiedModuleName, context.Start.Line);
808808
var undeclaredLocal =
809809
new Declaration(
810810
new QualifiedMemberName(enclosingProcedure.QualifiedName.QualifiedModuleName, identifierName),
@@ -859,7 +859,7 @@ public void AddUnboundContext(Declaration parentDeclaration, VBAParser.LExpressi
859859
}
860860

861861
var identifier = context.GetChild<VBAParser.UnrestrictedIdentifierContext>(0);
862-
var annotations = _annotationService.FindAnnotations(parentDeclaration.QualifiedName.QualifiedModuleName, context.Start.Line);
862+
var annotations = _identifierAnnotationService.FindAnnotations(parentDeclaration.QualifiedName.QualifiedModuleName, context.Start.Line);
863863

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

Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs

Lines changed: 11 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -159,12 +159,6 @@ protected void ResolveDeclarations(QualifiedModuleName module, IParseTree tree,
159159
{
160160
_state.AddDeclaration(createdDeclaration);
161161
}
162-
163-
//This is a hack to deal with annotations on module level variables.
164-
var memberAnnotations = declarationsListener.CreatedDeclarations
165-
.SelectMany(declaration => declaration.Annotations)
166-
.ToHashSet();
167-
moduleDeclaration.RemoveAnnotations(memberAnnotations);
168162
}
169163
catch (Exception exception)
170164
{
@@ -235,43 +229,25 @@ private static IEnumerable<IAnnotation> FindModuleAnnotations(IParseTree tree, I
235229
return null;
236230
}
237231

238-
var lastDeclarationsSectionLine = LastDeclarationsSectionLine(tree, annotations);
232+
var potentialModuleAnnotations = annotations.Where(annotation =>
233+
annotation.AnnotationType.HasFlag(AnnotationType.ModuleAnnotation));
234+
235+
var lastPossibleDeclarationsSectionLine = LastPossibleDeclarationsSectionLine(tree);
239236

240237
//There is no module body.
241-
if (lastDeclarationsSectionLine == null)
238+
if (lastPossibleDeclarationsSectionLine == null)
242239
{
243-
return annotations;
240+
return potentialModuleAnnotations;
244241
}
245242

246-
var lastPossibleModuleAnnotationLine = lastDeclarationsSectionLine.Value;
247-
var moduleAnnotations = annotations.Where(annotation => annotation.QualifiedSelection.Selection.EndLine <= lastPossibleModuleAnnotationLine);
248-
return moduleAnnotations.ToList();
243+
var lastPossibleModuleAnnotationLine = lastPossibleDeclarationsSectionLine.Value;
244+
var moduleAnnotations = potentialModuleAnnotations.Where(annotation => annotation.QualifiedSelection.Selection.EndLine <= lastPossibleModuleAnnotationLine);
245+
return moduleAnnotations;
249246
}
250247

251-
private static int? LastDeclarationsSectionLine(IParseTree tree, ICollection<IAnnotation> annotations)
248+
private static int? LastPossibleDeclarationsSectionLine(IParseTree tree)
252249
{
253-
var firstModuleBodyElementLine = FirstModuleBodyElementLine(tree);
254-
255-
if (firstModuleBodyElementLine == null)
256-
{
257-
return null;
258-
}
259-
260-
//The VBE uses 1-based lines.
261-
for (var currentLine = firstModuleBodyElementLine.Value - 1; currentLine >= 1; currentLine--)
262-
{
263-
if (annotations.Any(annotation => annotation.QualifiedSelection.Selection.StartLine <= currentLine
264-
&& annotation.QualifiedSelection.Selection.EndLine >=
265-
currentLine))
266-
{
267-
continue;
268-
}
269-
270-
return currentLine;
271-
}
272-
273-
//There is no declaration section.
274-
return 0;
250+
return FirstModuleBodyElementLine(tree) - 1;
275251
}
276252

277253
private static int? FirstModuleBodyElementLine(IParseTree tree)

Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs

Lines changed: 39 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,11 @@ public DeclarationSymbolsListener(
4343
}
4444

4545
private IEnumerable<IAnnotation> FindMemberAnnotations(int firstMemberLine)
46+
{
47+
return FindAnnotations(firstMemberLine, AnnotationType.MemberAnnotation);
48+
}
49+
50+
private IEnumerable<IAnnotation> FindAnnotations(int firstLine, AnnotationType annotationTypeFlag)
4651
{
4752
if (_annotations == null)
4853
{
@@ -52,22 +57,37 @@ private IEnumerable<IAnnotation> FindMemberAnnotations(int firstMemberLine)
5257
var annotations = new List<IAnnotation>();
5358

5459
// VBE 1-based indexing
55-
for (var currentLine = firstMemberLine - 1; currentLine >= 1; currentLine--)
60+
for (var currentLine = firstLine - 1; currentLine >= 1; currentLine--)
5661
{
62+
//Annotation sections end at the first line without an annotation with the specified flag or identifier annotation.
63+
//Identifier annotations are treated in a special way because identifier references can appear on the same line as other constructs that can be annotated.
5764
if (!_annotations.Any(annotation => annotation.QualifiedSelection.Selection.StartLine <= currentLine
58-
&& annotation.QualifiedSelection.Selection.EndLine >= currentLine))
65+
&& annotation.QualifiedSelection.Selection.EndLine >= currentLine
66+
&& (annotation.AnnotationType.HasFlag(annotationTypeFlag)
67+
|| annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation))))
5968
{
6069
break;
6170
}
6271

63-
var annotationsStartingOnCurrentLine = _annotations.Where(a => a.QualifiedSelection.Selection.StartLine == currentLine);
72+
var annotationsStartingOnCurrentLine = _annotations.Where(a => a.QualifiedSelection.Selection.StartLine == currentLine
73+
&& a.AnnotationType.HasFlag(annotationTypeFlag));
6474

6575
annotations.AddRange(annotationsStartingOnCurrentLine);
6676
}
6777

6878
return annotations;
6979
}
7080

81+
private IEnumerable<IAnnotation> FindVariableAnnotations(int firstVariableLine)
82+
{
83+
return FindAnnotations(firstVariableLine, AnnotationType.VariableAnnotation);
84+
}
85+
86+
private IEnumerable<IAnnotation> FindGeneralAnnotations(int firstLine)
87+
{
88+
return FindAnnotations(firstLine, AnnotationType.GeneralAnnotation);
89+
}
90+
7191
private Declaration CreateDeclaration(
7292
string identifierName,
7393
string asTypeName,
@@ -112,7 +132,6 @@ private Declaration CreateDeclaration(
112132
_attributes.TryGetValue(key, out var attributes);
113133
_membersAllowingAttributes.TryGetValue(key, out var attributesPassContext);
114134

115-
var annotations = FindMemberAnnotations(selection.StartLine);
116135
switch (declarationType)
117136
{
118137
case DeclarationType.Procedure:
@@ -125,8 +144,8 @@ private Declaration CreateDeclaration(
125144
context,
126145
attributesPassContext,
127146
selection,
128-
true,
129-
annotations,
147+
true,
148+
FindMemberAnnotations(selection.StartLine),
130149
attributes);
131150
break;
132151
case DeclarationType.Function:
@@ -143,7 +162,7 @@ private Declaration CreateDeclaration(
143162
selection,
144163
isArray,
145164
true,
146-
annotations,
165+
FindMemberAnnotations(selection.StartLine),
147166
attributes);
148167
break;
149168
case DeclarationType.Event:
@@ -159,7 +178,7 @@ private Declaration CreateDeclaration(
159178
selection,
160179
isArray,
161180
true,
162-
annotations,
181+
FindVariableAnnotations(selection.StartLine),
163182
attributes);
164183
break;
165184
case DeclarationType.LibraryProcedure:
@@ -174,8 +193,8 @@ private Declaration CreateDeclaration(
174193
accessibility,
175194
context,
176195
selection,
177-
true,
178-
annotations);
196+
true,
197+
FindMemberAnnotations(selection.StartLine));
179198
break;
180199
case DeclarationType.PropertyGet:
181200
result = new PropertyGetDeclaration(
@@ -191,7 +210,7 @@ private Declaration CreateDeclaration(
191210
selection,
192211
isArray,
193212
true,
194-
annotations,
213+
FindMemberAnnotations(selection.StartLine),
195214
attributes);
196215
break;
197216
case DeclarationType.PropertySet:
@@ -204,8 +223,8 @@ private Declaration CreateDeclaration(
204223
context,
205224
attributesPassContext,
206225
selection,
207-
true,
208-
annotations,
226+
true,
227+
FindMemberAnnotations(selection.StartLine),
209228
attributes);
210229
break;
211230
case DeclarationType.PropertyLet:
@@ -218,8 +237,8 @@ private Declaration CreateDeclaration(
218237
context,
219238
attributesPassContext,
220239
selection,
221-
true,
222-
annotations,
240+
true,
241+
FindMemberAnnotations(selection.StartLine),
223242
attributes);
224243
break;
225244
case DeclarationType.EnumerationMember:
@@ -229,8 +248,8 @@ private Declaration CreateDeclaration(
229248
_currentScope,
230249
asTypeName,
231250
asTypeContext,
232-
typeHint,
233-
annotations,
251+
typeHint,
252+
FindVariableAnnotations(selection.StartLine),
234253
accessibility,
235254
declarationType,
236255
(context as VBAParser.EnumerationStmt_ConstantContext)?.expression()?.GetText() ?? string.Empty,
@@ -252,7 +271,7 @@ private Declaration CreateDeclaration(
252271
selection,
253272
isArray,
254273
asTypeContext,
255-
annotations,
274+
FindVariableAnnotations(selection.StartLine),
256275
attributes);
257276
break;
258277
default:
@@ -272,7 +291,7 @@ private Declaration CreateDeclaration(
272291
isArray,
273292
asTypeContext,
274293
true,
275-
annotations,
294+
FindGeneralAnnotations(selection.StartLine),
276295
attributes);
277296
break;
278297
}
@@ -708,7 +727,7 @@ public override void EnterConstSubStmt(VBAParser.ConstSubStmtContext context)
708727
asTypeName,
709728
asTypeClause,
710729
typeHint,
711-
FindMemberAnnotations(constStmt.Start.Line),
730+
FindVariableAnnotations(constStmt.Start.Line),
712731
accessibility,
713732
DeclarationType.Constant,
714733
value,

0 commit comments

Comments
 (0)