Skip to content

Commit dda9300

Browse files
authored
Merge pull request #4648 from MDoerner/BetterMemberAnnotationScoping
Better member annotation scoping
2 parents 4213a8a + 46e5a9a commit dda9300

File tree

16 files changed

+449
-226
lines changed

16 files changed

+449
-226
lines changed

Rubberduck.CodeAnalysis/Inspections/Abstract/InspectionBase.cs

Lines changed: 15 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -86,28 +86,22 @@ protected virtual IEnumerable<Declaration> BuiltInDeclarations
8686

8787
protected bool IsIgnoringInspectionResultFor(QualifiedModuleName module, int line)
8888
{
89-
var annotations = State.GetModuleAnnotations(module).ToList();
90-
91-
if (State.GetModuleAnnotations(module) == null)
92-
{
93-
return false;
94-
}
95-
96-
// VBE 1-based indexing
97-
for (var i = line; i >= 1; i--)
89+
var lineScopedAnnotations = State.DeclarationFinder.FindAnnotations(module, line);
90+
foreach (var ignoreAnnotation in lineScopedAnnotations.OfType<IgnoreAnnotation>())
9891
{
99-
var annotation = annotations.SingleOrDefault(a => a.QualifiedSelection.Selection.StartLine == i);
100-
var ignoreAnnotation = annotation as IgnoreAnnotation;
101-
var ignoreModuleAnnotation = annotation as IgnoreModuleAnnotation;
102-
103-
if (ignoreAnnotation?.InspectionNames.Contains(AnnotationName) == true)
92+
if (ignoreAnnotation.InspectionNames.Contains(AnnotationName))
10493
{
10594
return true;
10695
}
96+
}
97+
98+
var moduleDeclaration = State.DeclarationFinder.Members(module)
99+
.First(decl => decl.DeclarationType.HasFlag(DeclarationType.Module));
107100

108-
if (ignoreModuleAnnotation != null
109-
&& (ignoreModuleAnnotation.InspectionNames.Contains(AnnotationName)
110-
|| !ignoreModuleAnnotation.InspectionNames.Any()))
101+
foreach (var ignoreModuleAnnotation in moduleDeclaration.Annotations.OfType<IgnoreModuleAnnotation>())
102+
{
103+
if (ignoreModuleAnnotation.InspectionNames.Contains(AnnotationName)
104+
|| !ignoreModuleAnnotation.InspectionNames.Any())
111105
{
112106
return true;
113107
}
@@ -119,7 +113,10 @@ protected bool IsIgnoringInspectionResultFor(QualifiedModuleName module, int lin
119113
protected bool IsIgnoringInspectionResultFor(Declaration declaration, string inspectionName)
120114
{
121115
var module = Declaration.GetModuleParent(declaration);
122-
if (module == null) { return false; }
116+
if (module == null)
117+
{
118+
return false;
119+
}
123120

124121
var isIgnoredAtModuleLevel = module.Annotations
125122
.Any(annotation => annotation.AnnotationType == AnnotationType.IgnoreModule

Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2525
var annotations = State.AllAnnotations;
2626

2727
var illegalAnnotations = UnboundAnnotations(annotations, userDeclarations, identifierReferences)
28-
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation));
28+
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation)
29+
|| annotation.AnnotatedLine == null);
2930

3031
return illegalAnnotations.Select(annotation =>
3132
new QualifiedContextInspectionResult(
Lines changed: 29 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
using Rubberduck.Parsing.Grammar;
1+
using System;
2+
using Rubberduck.Parsing.Grammar;
23
using Rubberduck.VBEditor;
34

45
namespace Rubberduck.Parsing.Annotations
@@ -7,19 +8,46 @@ public abstract class AnnotationBase : IAnnotation
78
{
89
public const string ANNOTATION_MARKER = "'@";
910

11+
private readonly Lazy<int?> _annotatedLine;
12+
1013
protected AnnotationBase(AnnotationType annotationType, QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context)
1114
{
1215
AnnotationType = annotationType;
1316
QualifiedSelection = qualifiedSelection;
1417
Context = context;
18+
_annotatedLine = new Lazy<int?>(GetAnnotatedLine);
1519
}
1620

1721
public AnnotationType AnnotationType { get; }
1822
public QualifiedSelection QualifiedSelection { get; }
1923
public VBAParser.AnnotationContext Context { get; }
2024

25+
public int? AnnotatedLine => _annotatedLine.Value;
26+
2127
public virtual bool AllowMultiple { get; } = false;
2228

2329
public override string ToString() => $"Annotation Type: {AnnotationType}";
30+
31+
32+
private int? GetAnnotatedLine()
33+
{
34+
var enclosingEndOfStatement = Context.GetAncestor<VBAParser.EndOfStatementContext>();
35+
36+
//Annotations on the same line as non-whitespace statements do not scope to anything.
37+
if (enclosingEndOfStatement.Start.TokenIndex != 0)
38+
{
39+
var firstEndOfLine = enclosingEndOfStatement.GetFirstEndOfLine();
40+
var parentEndOfLine = Context.GetAncestor<VBAParser.EndOfLineContext>();
41+
if (firstEndOfLine.Equals(parentEndOfLine))
42+
{
43+
return null;
44+
}
45+
}
46+
47+
var lastToken = enclosingEndOfStatement.stop;
48+
return lastToken.Type == VBAParser.NEWLINE
49+
? lastToken.Line + 1
50+
: lastToken.Line;
51+
}
2452
}
2553
}

Rubberduck.Parsing/Annotations/IAnnotation.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,5 +9,6 @@ public interface IAnnotation
99
QualifiedSelection QualifiedSelection { get; }
1010
bool AllowMultiple { get; }
1111
VBAParser.AnnotationContext Context { get; }
12+
int? AnnotatedLine { get; }
1213
}
1314
}

Rubberduck.Parsing/Annotations/IdentifierAnnotationService.cs

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

Rubberduck.Parsing/ParserRuleContextExtensions.cs

Lines changed: 50 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -197,8 +197,31 @@ public static bool ContainsTokenIndex(this ParserRuleContext context, int tokenI
197197
/// </summary>
198198
public static TContext GetDescendent<TContext>(this ParserRuleContext context) where TContext : ParserRuleContext
199199
{
200-
var descendents = GetDescendents<TContext>(context);
201-
return descendents.OrderBy(descendent => descendent.Start.TokenIndex).FirstOrDefault();
200+
if (context?.children == null)
201+
{
202+
return null;
203+
}
204+
205+
foreach (var child in context.children)
206+
{
207+
if (child == null)
208+
{
209+
continue;
210+
}
211+
212+
if (child is TContext match)
213+
{
214+
return match;
215+
}
216+
217+
var childResult = (child as ParserRuleContext)?.GetDescendent<TContext>();
218+
if (childResult != null)
219+
{
220+
return childResult;
221+
}
222+
}
223+
224+
return null;
202225
}
203226

204227
/// <summary>
@@ -221,6 +244,31 @@ public static bool TryGetChildContext<TContext>(this ParserRuleContext ctxt, out
221244
return opCtxt != null;
222245
}
223246

247+
/// <summary>
248+
/// Returns the endOfStatementContext's first endOfLine context.
249+
/// </summary>
250+
public static VBAParser.EndOfLineContext GetFirstEndOfLine(this VBAParser.EndOfStatementContext endOfStatement)
251+
{
252+
//This dedicated method exists for performance reasons on hot-paths.
253+
var individualEndOfStatements = endOfStatement.individualNonEOFEndOfStatement();
254+
255+
if (individualEndOfStatements == null)
256+
{
257+
return null;
258+
}
259+
260+
foreach (var individualEndOfStatement in individualEndOfStatements)
261+
{
262+
var endOfLine = individualEndOfStatement.endOfLine();
263+
if (endOfLine != null)
264+
{
265+
return endOfLine;
266+
}
267+
}
268+
//The only remaining alternative is whitespace followed by an EOF.
269+
return null;
270+
}
271+
224272
/// <summary>
225273
/// Determines if the context's module declares or defaults to
226274
/// Option Compare Binary

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: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -22,13 +22,12 @@ 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;
2928
private readonly ConcurrentBag<UnboundMemberDeclaration> _newUnresolved;
3029
private List<UnboundMemberDeclaration> _unresolved;
31-
private IDictionary<QualifiedModuleName, List<IAnnotation>> _annotations;
30+
private IDictionary<(QualifiedModuleName module, int annotatedLine), List<IAnnotation>> _annotations;
3231
private IDictionary<Declaration, List<ParameterDeclaration>> _parametersByParent;
3332
private IDictionary<DeclarationType, List<Declaration>> _userDeclarationsByType;
3433
private IDictionary<QualifiedSelection, List<Declaration>> _declarationsBySelection;
@@ -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

@@ -92,7 +89,8 @@ private List<Action> CollectionConstructionActions(IReadOnlyList<Declaration> de
9289
.ToList(),
9390
() =>
9491
_annotations = annotations
95-
.GroupBy(node => node.QualifiedSelection.QualifiedName)
92+
.Where(a => a.AnnotatedLine.HasValue)
93+
.GroupBy(a => (a.QualifiedSelection.QualifiedName, a.AnnotatedLine.Value))
9694
.ToDictionary(),
9795
() =>
9896
_declarations = declarations
@@ -489,9 +487,9 @@ public IEnumerable<Declaration> FindMemberMatches(Declaration parent, string mem
489487
: Enumerable.Empty<Declaration>();
490488
}
491489

492-
public IEnumerable<IAnnotation> FindAnnotations(QualifiedModuleName module)
490+
public IEnumerable<IAnnotation> FindAnnotations(QualifiedModuleName module, int annotatedLine)
493491
{
494-
return _annotations.TryGetValue(module, out var result)
492+
return _annotations.TryGetValue((module, annotatedLine), out var result)
495493
? result
496494
: Enumerable.Empty<IAnnotation>();
497495
}
@@ -814,7 +812,8 @@ public Declaration FindMemberEnclosingProcedure(Declaration enclosingProcedure,
814812

815813
public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string identifierName, ParserRuleContext context)
816814
{
817-
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));
818817
var undeclaredLocal =
819818
new Declaration(
820819
new QualifiedMemberName(enclosingProcedure.QualifiedName.QualifiedModuleName, identifierName),
@@ -869,7 +868,8 @@ public void AddUnboundContext(Declaration parentDeclaration, VBAParser.LExpressi
869868
}
870869

871870
var identifier = context.GetChild<VBAParser.UnrestrictedIdentifierContext>(0);
872-
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));
873873

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

0 commit comments

Comments
 (0)