Skip to content

Commit 80896f2

Browse files
authored
Merge pull request #4412 from MDoerner/RecognizeNonExostentAnnotationsAsIllegal
Recognize non existent annotations as illegal
2 parents c623514 + 18239ca commit 80896f2

File tree

16 files changed

+637
-172
lines changed

16 files changed

+637
-172
lines changed
Lines changed: 84 additions & 146 deletions
Original file line numberDiff line numberDiff line change
@@ -1,175 +1,113 @@
1-
using System;
21
using System.Collections.Generic;
3-
using System.Diagnostics;
42
using System.Linq;
5-
using Antlr4.Runtime;
63
using Rubberduck.Inspections.Abstract;
74
using Rubberduck.Inspections.Results;
85
using Rubberduck.Parsing;
96
using Rubberduck.Parsing.Annotations;
10-
using Rubberduck.Parsing.Grammar;
117
using Rubberduck.Parsing.Inspections.Abstract;
12-
using Rubberduck.Resources.Inspections;
138
using Rubberduck.Parsing.Symbols;
9+
using Rubberduck.Resources.Inspections;
1410
using Rubberduck.Parsing.VBA;
15-
using Rubberduck.VBEditor;
11+
using Rubberduck.Parsing.VBA.Extensions;
1612

1713
namespace Rubberduck.Inspections.Concrete
1814
{
19-
public sealed class IllegalAnnotationInspection : ParseTreeInspectionBase
15+
public sealed class IllegalAnnotationInspection : InspectionBase
2016
{
2117
public IllegalAnnotationInspection(RubberduckParserState state)
2218
: base(state)
23-
{
24-
Listener = new IllegalAttributeAnnotationsListener(state);
25-
}
26-
27-
public override IInspectionListener Listener { get; }
19+
{}
2820

2921
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3022
{
31-
return Listener.Contexts.Select(context =>
32-
new QualifiedContextInspectionResult(this,
33-
string.Format(InspectionResults.IllegalAnnotationInspection, ((VBAParser.AnnotationContext)context.Context).annotationName().GetText()), context));
23+
var illegalAnnotations = new List<IAnnotation>();
24+
25+
var userDeclarations = State.DeclarationFinder.AllUserDeclarations.ToList();
26+
var identifierReferences = State.DeclarationFinder.AllIdentifierReferences().ToList();
27+
var annotations = State.AllAnnotations;
28+
29+
illegalAnnotations.AddRange(UnboundAnnotations(annotations, userDeclarations, identifierReferences));
30+
illegalAnnotations.AddRange(NonIdentifierAnnotationsOnIdentifiers(identifierReferences));
31+
illegalAnnotations.AddRange(NonModuleAnnotationsOnModules(userDeclarations));
32+
illegalAnnotations.AddRange(NonMemberAnnotationsOnMembers(userDeclarations));
33+
illegalAnnotations.AddRange(NonVariableAnnotationsOnVariables(userDeclarations));
34+
illegalAnnotations.AddRange(NonGeneralAnnotationsWhereOnlyGeneralAnnotationsBelong(userDeclarations));
35+
36+
return illegalAnnotations.Select(annotation =>
37+
new QualifiedContextInspectionResult(
38+
this,
39+
string.Format(InspectionResults.IllegalAnnotationInspection, annotation.Context.annotationName().GetText()),
40+
new QualifiedContext(annotation.QualifiedSelection.QualifiedName, annotation.Context)));
3441
}
3542

36-
public class IllegalAttributeAnnotationsListener : VBAParserBaseListener, IInspectionListener
43+
private static ICollection<IAnnotation> UnboundAnnotations(IEnumerable<IAnnotation> annotations, IEnumerable<Declaration> userDeclarations, IEnumerable<IdentifierReference> identifierReferences)
3744
{
38-
private readonly RubberduckParserState _state;
39-
40-
private Lazy<Declaration> _module;
41-
private Lazy<IDictionary<string, Declaration>> _members;
42-
43-
public IllegalAttributeAnnotationsListener(RubberduckParserState state)
44-
{
45-
_state = state;
46-
}
47-
48-
private readonly List<QualifiedContext<ParserRuleContext>> _contexts =
49-
new List<QualifiedContext<ParserRuleContext>>();
50-
51-
public IReadOnlyList<QualifiedContext<ParserRuleContext>> Contexts => _contexts;
52-
53-
public QualifiedModuleName CurrentModuleName { get; set; }
54-
55-
private bool _isFirstMemberProcessed;
56-
57-
public void ClearContexts()
58-
{
59-
_contexts.Clear();
60-
_isFirstMemberProcessed = false;
61-
}
62-
63-
#region scoping
64-
private Declaration _currentScopeDeclaration;
65-
private bool _hasMembers;
66-
67-
private void SetCurrentScope(string memberName = null)
68-
{
69-
_hasMembers = !string.IsNullOrEmpty(memberName);
70-
// this is a one-time toggle until contexts are reset
71-
_isFirstMemberProcessed |= _hasMembers;
72-
_currentScopeDeclaration = _hasMembers ? _members.Value[memberName] : _module.Value;
73-
}
74-
75-
public override void EnterModuleBody(VBAParser.ModuleBodyContext context)
76-
{
77-
_currentScopeDeclaration = _state.DeclarationFinder
78-
.UserDeclarations(DeclarationType.Procedure)
79-
.Where(declaration => declaration.QualifiedName.QualifiedModuleName.Equals(CurrentModuleName))
80-
.OrderBy(declaration => declaration.Selection)
81-
.FirstOrDefault();
82-
}
83-
84-
public override void EnterModule(VBAParser.ModuleContext context)
85-
{
86-
_module = new Lazy<Declaration>(() => _state.DeclarationFinder
87-
.UserDeclarations(DeclarationType.Module)
88-
.SingleOrDefault(m => m.QualifiedName.QualifiedModuleName.Equals(CurrentModuleName)));
89-
90-
_members = new Lazy<IDictionary<string, Declaration>>(() => _state.DeclarationFinder
91-
.Members(CurrentModuleName)
92-
.GroupBy(m => m.IdentifierName)
93-
.ToDictionary(m => m.Key, m => m.First()));
94-
95-
// we did not process the first member of the module we just entered, so reset here
96-
_isFirstMemberProcessed = false;
97-
}
98-
99-
public override void ExitModule(VBAParser.ModuleContext context)
100-
{
101-
_currentScopeDeclaration = null;
102-
}
103-
104-
public override void EnterModuleAttributes(VBAParser.ModuleAttributesContext context)
105-
{
106-
// note: using ModuleAttributesContext for module-scope
107-
108-
if(_currentScopeDeclaration == null)
109-
{
110-
// we're at the top of the module.
111-
// everything we pick up between here and the module body, is module-scoped:
112-
_currentScopeDeclaration = _state.DeclarationFinder.UserDeclarations(DeclarationType.Module)
113-
.SingleOrDefault(d => d.QualifiedName.QualifiedModuleName.Equals(CurrentModuleName));
114-
}
115-
else
116-
{
117-
// DO NOT re-assign _currentScope here.
118-
// we're at the end of the module and that attribute is actually scoped to the last procedure.
119-
Debug.Assert(_currentScopeDeclaration != null); // deliberate no-op
120-
}
121-
}
122-
123-
public override void EnterSubStmt(VBAParser.SubStmtContext context)
124-
{
125-
SetCurrentScope(Identifier.GetName(context.subroutineName()));
126-
}
127-
128-
public override void EnterFunctionStmt(VBAParser.FunctionStmtContext context)
129-
{
130-
SetCurrentScope(Identifier.GetName(context.functionName()));
131-
}
132-
133-
public override void EnterPropertyGetStmt(VBAParser.PropertyGetStmtContext context)
134-
{
135-
SetCurrentScope(Identifier.GetName(context.functionName()));
136-
}
137-
138-
public override void EnterPropertyLetStmt(VBAParser.PropertyLetStmtContext context)
139-
{
140-
SetCurrentScope(Identifier.GetName(context.subroutineName()));
141-
}
142-
143-
public override void EnterPropertySetStmt(VBAParser.PropertySetStmtContext context)
144-
{
145-
SetCurrentScope(Identifier.GetName(context.subroutineName()));
146-
}
147-
#endregion
148-
149-
public override void ExitAnnotation(VBAParser.AnnotationContext context)
150-
{
151-
var name = Identifier.GetName(context.annotationName().unrestrictedIdentifier());
152-
var annotationType = (AnnotationType) Enum.Parse(typeof (AnnotationType), name, true);
153-
154-
var moduleHasMembers = _members.Value.Any();
45+
var boundAnnotationsSelections = userDeclarations
46+
.SelectMany(declaration => declaration.Annotations)
47+
.Concat(identifierReferences.SelectMany(reference => reference.Annotations))
48+
.Select(annotation => annotation.QualifiedSelection)
49+
.ToHashSet();
50+
51+
return annotations.Where(annotation => !boundAnnotationsSelections.Contains(annotation.QualifiedSelection)).ToList();
52+
}
15553

156-
var isMemberAnnotation = annotationType.HasFlag(AnnotationType.MemberAnnotation);
157-
var isModuleAnnotation = annotationType.HasFlag(AnnotationType.ModuleAnnotation);
54+
private static ICollection<IAnnotation> NonIdentifierAnnotationsOnIdentifiers(IEnumerable<IdentifierReference> identifierReferences)
55+
{
56+
return identifierReferences
57+
.SelectMany(reference => reference.Annotations)
58+
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation))
59+
.ToList();
60+
}
15861

159-
var isModuleAnnotatedForMemberAnnotation = isMemberAnnotation
160-
&& (_currentScopeDeclaration?.DeclarationType.HasFlag(DeclarationType.Module) ?? false);
62+
private static ICollection<IAnnotation> NonModuleAnnotationsOnModules(IEnumerable<Declaration> userDeclarations)
63+
{
64+
return userDeclarations
65+
.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Module))
66+
.SelectMany(moduleDeclaration => moduleDeclaration.Annotations)
67+
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.ModuleAnnotation))
68+
.ToList();
69+
}
16170

162-
var isMemberAnnotatedForModuleAnnotation = isModuleAnnotation
163-
&& (_currentScopeDeclaration?.DeclarationType.HasFlag(DeclarationType.Member) ?? false);
71+
private static ICollection<IAnnotation> NonMemberAnnotationsOnMembers(IEnumerable<Declaration> userDeclarations)
72+
{
73+
return userDeclarations
74+
.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Member))
75+
.SelectMany(member => member.Annotations)
76+
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.MemberAnnotation))
77+
.ToList();
78+
}
16479

165-
var isIllegal = !(isMemberAnnotation && moduleHasMembers && !_isFirstMemberProcessed) &&
166-
(isMemberAnnotatedForModuleAnnotation || isModuleAnnotatedForMemberAnnotation);
80+
private static ICollection<IAnnotation> NonVariableAnnotationsOnVariables(IEnumerable<Declaration> userDeclarations)
81+
{
82+
return userDeclarations
83+
.Where(declaration => VariableAnnotationDeclarationTypes.Contains(declaration.DeclarationType))
84+
.SelectMany(declaration => declaration.Annotations)
85+
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.VariableAnnotation))
86+
.ToList();
87+
}
16788

168-
if (isIllegal)
169-
{
170-
_contexts.Add(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context));
171-
}
172-
}
89+
private static readonly HashSet<DeclarationType> VariableAnnotationDeclarationTypes = new HashSet<DeclarationType>()
90+
{
91+
DeclarationType.Variable,
92+
DeclarationType.Control,
93+
DeclarationType.Constant,
94+
DeclarationType.Enumeration,
95+
DeclarationType.EnumerationMember,
96+
DeclarationType.UserDefinedType,
97+
DeclarationType.UserDefinedType,
98+
DeclarationType.UserDefinedTypeMember
99+
};
100+
101+
private static ICollection<IAnnotation> NonGeneralAnnotationsWhereOnlyGeneralAnnotationsBelong(IEnumerable<Declaration> userDeclarations)
102+
{
103+
return userDeclarations
104+
.Where(declaration => !declaration.DeclarationType.HasFlag(DeclarationType.Module)
105+
&& !declaration.DeclarationType.HasFlag(DeclarationType.Member)
106+
&& !VariableAnnotationDeclarationTypes.Contains(declaration.DeclarationType)
107+
&& declaration.DeclarationType != DeclarationType.Project)
108+
.SelectMany(member => member.Annotations)
109+
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation))
110+
.ToList();
173111
}
174112
}
175113
}

Rubberduck.Parsing/Annotations/AnnotationListener.cs

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -23,11 +23,7 @@ public AnnotationListener(IAnnotationFactory factory, QualifiedModuleName qualif
2323
public override void ExitAnnotation([NotNull] VBAParser.AnnotationContext context)
2424
{
2525
var newAnnotation = _factory.Create(context, new QualifiedSelection(_qualifiedName, context.GetSelection()));
26-
// It might be an annotation we don't support or a typo.
27-
if (newAnnotation != null)
28-
{
29-
_annotations.Add(newAnnotation);
30-
}
26+
_annotations.Add(newAnnotation);
3127
}
3228
}
3329
}

Rubberduck.Parsing/Annotations/AnnotationService.cs

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -20,14 +20,17 @@ public IEnumerable<IAnnotation> FindAnnotations(QualifiedModuleName module, int
2020
var annotations = new List<IAnnotation>();
2121
var moduleAnnotations = _declarationFinder.FindAnnotations(module).ToList();
2222
// VBE 1-based indexing
23-
for (var i = line - 1; i >= 1; i--)
23+
for (var currentLine = line - 1; currentLine >= 1; currentLine--)
2424
{
25-
var annotation = moduleAnnotations.SingleOrDefault(a => a.QualifiedSelection.Selection.StartLine == i);
26-
if (annotation == null)
25+
if (!moduleAnnotations.Any(annotation => annotation.QualifiedSelection.Selection.StartLine <= currentLine
26+
&& annotation.QualifiedSelection.Selection.EndLine >= currentLine))
2727
{
2828
break;
2929
}
30-
annotations.Add(annotation);
30+
31+
var annotationsStartingOnCurrentLine = moduleAnnotations.Where(a => a.QualifiedSelection.Selection.StartLine == currentLine);
32+
33+
annotations.AddRange(annotationsStartingOnCurrentLine);
3134
}
3235
return annotations;
3336
}

Rubberduck.Parsing/Annotations/AnnotationType.cs

Lines changed: 27 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -8,18 +8,39 @@ namespace Rubberduck.Parsing.Annotations
88
public enum AnnotationType
99
{
1010
/// <summary>
11-
/// A flag indicating that the annotation type is valid for module.
11+
/// A type for all not recognized annotations.
12+
/// </summary>
13+
NotRecognized = 0,
14+
15+
/// <summary>
16+
/// A flag indicating that the annotation type is valid for modules.
1217
/// </summary>
1318
ModuleAnnotation = 1 << 1,
19+
1420
/// <summary>
15-
/// A flag indicating that the annotation type is valid for member.
21+
/// A flag indicating that the annotation type is valid for members (method).
1622
/// </summary>
1723
MemberAnnotation = 1 << 2,
1824

25+
/// <summary>
26+
/// A flag indicating that the annotation type is valid for variables or constants.
27+
/// </summary>
28+
VariableAnnotation = 1 << 3,
29+
30+
/// <summary>
31+
/// A flag indicating that the annotation type is valid for identifier references.
32+
/// </summary>
33+
IdentifierAnnotation = 1 << 4,
34+
35+
/// <summary>
36+
/// A flag indicating that the annotation type is valid on everything but modules.
37+
/// </summary>
38+
GeneralAnnotation = 1 << 5 | MemberAnnotation | VariableAnnotation | IdentifierAnnotation,
39+
1940
/// <summary>
2041
/// A flag indicating that the annotation type is driving an attribute.
2142
/// </summary>
22-
Attribute = 1 << 4,
43+
Attribute = 1 << 6,
2344

2445
TestModule = 1 << 8 | ModuleAnnotation,
2546
ModuleInitialize = 1 << 9 | MemberAnnotation,
@@ -28,7 +49,7 @@ public enum AnnotationType
2849
TestInitialize = 1 << 12 | MemberAnnotation,
2950
TestCleanup = 1 << 13 | MemberAnnotation,
3051
IgnoreTest = 1 << 14 | MemberAnnotation,
31-
Ignore = 1 << 15,
52+
Ignore = 1 << 15 | GeneralAnnotation,
3253
IgnoreModule = 1 << 16 | ModuleAnnotation,
3354
Folder = 1 << 17 | ModuleAnnotation,
3455
NoIndent = 1 << 18 | ModuleAnnotation,
@@ -43,7 +64,7 @@ public enum AnnotationType
4364
PredeclaredId = 1 << 16 | Attribute | ModuleAnnotation,
4465
[AttributeAnnotation("VB_Exposed", "True")]
4566
Exposed = 1 << 17 | Attribute | ModuleAnnotation,
46-
Obsolete = 1 << 18 | MemberAnnotation
67+
Obsolete = 1 << 18 | MemberAnnotation | VariableAnnotation
4768
}
4869

4970
[AttributeUsage(AttributeTargets.Field)]
@@ -53,7 +74,7 @@ public class AttributeAnnotationAttribute : Attribute
5374
/// Enum value is associated with a VB_Attribute.
5475
/// </summary>
5576
/// <param name="name">The name of the associated attribute.</param>
56-
/// <param name="value">If specified, contrains the association to a specific value.</param>
77+
/// <param name="value">If specified, constrains the association to a specific value.</param>
5778
public AttributeAnnotationAttribute(string name, string value = null)
5879
{
5980
AttributeName = name;
Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
using Rubberduck.VBEditor;
2+
using System.Collections.Generic;
3+
using Rubberduck.Parsing.Grammar;
4+
5+
namespace Rubberduck.Parsing.Annotations
6+
{
7+
/// <summary>
8+
/// Used for all annotations not recognized by RD.
9+
/// </summary>
10+
public sealed class NotRecognizedAnnotation : AnnotationBase
11+
{
12+
public NotRecognizedAnnotation(
13+
QualifiedSelection qualifiedSelection,
14+
VBAParser.AnnotationContext context,
15+
IEnumerable<string> parameters)
16+
: base(AnnotationType.NotRecognized, qualifiedSelection, context)
17+
{}
18+
}
19+
}

Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,7 @@ private IAnnotation CreateAnnotation(string annotationName, List<string> paramet
5858
return (IAnnotation) Activator.CreateInstance(annotationClrType, qualifiedSelection, context, parameters);
5959
}
6060

61-
return null;
61+
return new NotRecognizedAnnotation(qualifiedSelection, context, parameters);
6262
}
6363
}
6464
}

0 commit comments

Comments
 (0)