Skip to content

Commit 84cf953

Browse files
committed
Scope annotations to next non-whitespace line
This also deems all annotations on non-whitespace lines illegal. The reasoning behind this change is that the previous system was somewhat unintuitive and fragile in that comments and non-member annotations could break a member annotation section. This is inconvenient in particular when removing annotations with a comment on the same line. Moreover, the new scoping is better aligned with VBE's own procedure separators. As a side-effect, the logic for determining the annotated line has been centralized and simplified. In addition, stacking identifier annotations along a procedure is no longer possible, which could be problematic before.
1 parent 4a6976f commit 84cf953

File tree

11 files changed

+351
-167
lines changed

11 files changed

+351
-167
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.GetDescendent<VBAParser.EndOfLineContext>();
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: 1 addition & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -16,24 +16,7 @@ public IdentifierAnnotationService(DeclarationFinder declarationFinder)
1616

1717
public IEnumerable<IAnnotation> FindAnnotations(QualifiedModuleName module, int line)
1818
{
19-
var annotations = new List<IAnnotation>();
20-
var moduleAnnotations = _declarationFinder.FindAnnotations(module).ToList();
21-
// VBE 1-based indexing
22-
for (var currentLine = line - 1; currentLine >= 1; currentLine--)
23-
{
24-
//Identifier annotation sections end at the first line above without an identifier annotation.
25-
if (!moduleAnnotations.Any(annotation => annotation.QualifiedSelection.Selection.StartLine <= currentLine
26-
&& annotation.QualifiedSelection.Selection.EndLine >= currentLine
27-
&& annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation)))
28-
{
29-
break;
30-
}
31-
32-
var annotationsStartingOnCurrentLine = moduleAnnotations.Where(a => a.QualifiedSelection.Selection.StartLine == currentLine && a.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation));
33-
34-
annotations.AddRange(annotationsStartingOnCurrentLine);
35-
}
36-
return annotations;
19+
return _declarationFinder.FindAnnotations(module, line).Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation));
3720
}
3821
}
3922
}

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ public class DeclarationFinder
2828
private readonly ConcurrentDictionary<QualifiedMemberName, ConcurrentBag<Declaration>> _newUndeclared;
2929
private readonly ConcurrentBag<UnboundMemberDeclaration> _newUnresolved;
3030
private List<UnboundMemberDeclaration> _unresolved;
31-
private IDictionary<QualifiedModuleName, List<IAnnotation>> _annotations;
31+
private IDictionary<(QualifiedModuleName module, int annotatedLine), List<IAnnotation>> _annotations;
3232
private IDictionary<Declaration, List<ParameterDeclaration>> _parametersByParent;
3333
private IDictionary<DeclarationType, List<Declaration>> _userDeclarationsByType;
3434
private IDictionary<QualifiedSelection, List<Declaration>> _declarationsBySelection;
@@ -92,7 +92,8 @@ private List<Action> CollectionConstructionActions(IReadOnlyList<Declaration> de
9292
.ToList(),
9393
() =>
9494
_annotations = annotations
95-
.GroupBy(node => node.QualifiedSelection.QualifiedName)
95+
.Where(a => a.AnnotatedLine.HasValue)
96+
.GroupBy(a => (a.QualifiedSelection.QualifiedName, a.AnnotatedLine.Value))
9697
.ToDictionary(),
9798
() =>
9899
_declarations = declarations
@@ -489,9 +490,9 @@ public IEnumerable<Declaration> FindMemberMatches(Declaration parent, string mem
489490
: Enumerable.Empty<Declaration>();
490491
}
491492

492-
public IEnumerable<IAnnotation> FindAnnotations(QualifiedModuleName module)
493+
public IEnumerable<IAnnotation> FindAnnotations(QualifiedModuleName module, int annotatedLine)
493494
{
494-
return _annotations.TryGetValue(module, out var result)
495+
return _annotations.TryGetValue((module, annotatedLine), out var result)
495496
? result
496497
: Enumerable.Empty<IAnnotation>();
497498
}

Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs

Lines changed: 20 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -140,11 +140,14 @@ protected void ResolveDeclarations(QualifiedModuleName module, IParseTree tree,
140140
}
141141
Logger.Debug($"Creating declarations for module {module.Name}.");
142142

143-
var annotations = _state.GetModuleAnnotations(module).ToList();
143+
var annotationsOnWhiteSpaceLines = _state.GetModuleAnnotations(module)
144+
.Where(a => a.AnnotatedLine.HasValue)
145+
.GroupBy(a => a.AnnotatedLine.Value)
146+
.ToDictionary();
144147
var attributes = _state.GetModuleAttributes(module);
145148
var membersAllowingAttributes = _state.GetMembersAllowingAttributes(module);
146149

147-
var moduleDeclaration = NewModuleDeclaration(module, tree, annotations, attributes, projectDeclaration);
150+
var moduleDeclaration = NewModuleDeclaration(module, tree, annotationsOnWhiteSpaceLines, attributes, projectDeclaration);
148151
_state.AddDeclaration(moduleDeclaration);
149152

150153
var controlDeclarations = DeclarationsFromControls(moduleDeclaration);
@@ -153,7 +156,7 @@ protected void ResolveDeclarations(QualifiedModuleName module, IParseTree tree,
153156
_state.AddDeclaration(declaration);
154157
}
155158

156-
var declarationsListener = new DeclarationSymbolsListener(moduleDeclaration, annotations, attributes, membersAllowingAttributes);
159+
var declarationsListener = new DeclarationSymbolsListener(moduleDeclaration, annotationsOnWhiteSpaceLines, attributes, membersAllowingAttributes);
157160
ParseTreeWalker.Default.Walk(declarationsListener, tree);
158161
foreach (var createdDeclaration in declarationsListener.CreatedDeclarations)
159162
{
@@ -172,13 +175,13 @@ protected void ResolveDeclarations(QualifiedModuleName module, IParseTree tree,
172175
private ModuleDeclaration NewModuleDeclaration(
173176
QualifiedModuleName qualifiedModuleName,
174177
IParseTree tree,
175-
ICollection<IAnnotation> annotations,
178+
IDictionary<int, List<IAnnotation>> annotationsOnWhiteSpaceLines,
176179
IDictionary<(string scopeIdentifier, DeclarationType scopeType),
177180
Attributes> attributes,
178181
Declaration projectDeclaration)
179182
{
180183
var moduleAttributes = ModuleAttributes(qualifiedModuleName, attributes);
181-
var moduleAnnotations = FindModuleAnnotations(tree, annotations);
184+
var moduleAnnotations = FindModuleAnnotations(tree, annotationsOnWhiteSpaceLines);
182185

183186
switch (qualifiedModuleName.ComponentType)
184187
{
@@ -222,34 +225,30 @@ private static Attributes ModuleAttributes(QualifiedModuleName qualifiedModuleNa
222225
return moduleAttributes;
223226
}
224227

225-
private static IEnumerable<IAnnotation> FindModuleAnnotations(IParseTree tree, ICollection<IAnnotation> annotations)
228+
private static IEnumerable<IAnnotation> FindModuleAnnotations(IParseTree tree, IDictionary<int, List<IAnnotation>> annotationsOnWhiteSpaceLines)
226229
{
227-
if (annotations == null)
230+
if (annotationsOnWhiteSpaceLines == null)
228231
{
229232
return null;
230233
}
231234

232-
var potentialModuleAnnotations = annotations.Where(annotation =>
233-
annotation.AnnotationType.HasFlag(AnnotationType.ModuleAnnotation));
235+
var firstModuleBodyLine = FirstModuleBodyElementLine(tree);
234236

235-
var lastPossibleDeclarationsSectionLine = LastPossibleDeclarationsSectionLine(tree);
236-
237-
//There is no module body.
238-
if (lastPossibleDeclarationsSectionLine == null)
237+
//There is no module body and, thus, no restrictions on the placement of module annotations on whitespace lines.
238+
if (firstModuleBodyLine == null)
239239
{
240-
return potentialModuleAnnotations;
240+
return annotationsOnWhiteSpaceLines.Values.SelectMany(annotationList => annotationList)
241+
.Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.ModuleAnnotation));
241242
}
242243

243-
var lastPossibleModuleAnnotationLine = lastPossibleDeclarationsSectionLine.Value;
244-
var moduleAnnotations = potentialModuleAnnotations.Where(annotation => annotation.QualifiedSelection.Selection.EndLine <= lastPossibleModuleAnnotationLine);
244+
var lastPossibleAnnotatedLine = firstModuleBodyLine.Value;
245+
var moduleAnnotations = annotationsOnWhiteSpaceLines.Keys
246+
.Where(line => (line <= lastPossibleAnnotatedLine))
247+
.SelectMany(line => annotationsOnWhiteSpaceLines[line])
248+
.Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.ModuleAnnotation));
245249
return moduleAnnotations;
246250
}
247251

248-
private static int? LastPossibleDeclarationsSectionLine(IParseTree tree)
249-
{
250-
return FirstModuleBodyElementLine(tree) - 1;
251-
}
252-
253252
private static int? FirstModuleBodyElementLine(IParseTree tree)
254253
{
255254
var startContext = (ParserRuleContext)tree;

Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs

Lines changed: 5 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ public class DeclarationSymbolsListener : VBAParserBaseListener
1818
private Declaration _currentScopeDeclaration;
1919
private Declaration _parentDeclaration;
2020

21-
private readonly ICollection<IAnnotation> _annotations;
21+
private readonly IDictionary<int, List<IAnnotation>> _annotations;
2222
private readonly IDictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes> _attributes;
2323
private readonly IDictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext> _membersAllowingAttributes;
2424

@@ -27,7 +27,7 @@ public class DeclarationSymbolsListener : VBAParserBaseListener
2727

2828
public DeclarationSymbolsListener(
2929
Declaration moduleDeclaration,
30-
ICollection<IAnnotation> annotations,
30+
IDictionary<int, List<IAnnotation>> annotations,
3131
IDictionary<(string scopeIdentifier, DeclarationType scopeType),
3232
Attributes> attributes,
3333
IDictionary<(string scopeIdentifier, DeclarationType scopeType),
@@ -54,28 +54,12 @@ private IEnumerable<IAnnotation> FindAnnotations(int firstLine, AnnotationType a
5454
return null;
5555
}
5656

57-
var annotations = new List<IAnnotation>();
58-
59-
// VBE 1-based indexing
60-
for (var currentLine = firstLine - 1; currentLine >= 1; currentLine--)
57+
if (_annotations.TryGetValue(firstLine, out var scopedAnnotations))
6158
{
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.
64-
if (!_annotations.Any(annotation => annotation.QualifiedSelection.Selection.StartLine <= currentLine
65-
&& annotation.QualifiedSelection.Selection.EndLine >= currentLine
66-
&& (annotation.AnnotationType.HasFlag(annotationTypeFlag)
67-
|| annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation))))
68-
{
69-
break;
70-
}
71-
72-
var annotationsStartingOnCurrentLine = _annotations.Where(a => a.QualifiedSelection.Selection.StartLine == currentLine
73-
&& a.AnnotationType.HasFlag(annotationTypeFlag));
74-
75-
annotations.AddRange(annotationsStartingOnCurrentLine);
59+
return scopedAnnotations.Where(annotation => annotation.AnnotationType.HasFlag(annotationTypeFlag));
7660
}
7761

78-
return annotations;
62+
return Enumerable.Empty<IAnnotation>();
7963
}
8064

8165
private IEnumerable<IAnnotation> FindVariableAnnotations(int firstVariableLine)

0 commit comments

Comments
 (0)