Skip to content

Commit 0c7da5a

Browse files
committed
Make IllegalAnnotationInspection work for individual modules
1 parent 46d3707 commit 0c7da5a

File tree

6 files changed

+64
-23
lines changed

6 files changed

+64
-23
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs

Lines changed: 53 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,8 @@
99
using Rubberduck.Parsing.Symbols;
1010
using Rubberduck.Resources.Inspections;
1111
using Rubberduck.Parsing.VBA;
12+
using Rubberduck.Parsing.VBA.DeclarationCaching;
13+
using Rubberduck.VBEditor;
1214
using Rubberduck.VBEditor.SafeComWrappers;
1315

1416
namespace Rubberduck.Inspections.Concrete
@@ -53,27 +55,65 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5355
{
5456
var finder = DeclarationFinderProvider.DeclarationFinder;
5557

56-
var userDeclarations = finder.AllUserDeclarations.ToList();
57-
var identifierReferences = finder.AllIdentifierReferences().ToList();
58-
var annotations = _state.AllAnnotations;
58+
return finder.UserDeclarations(DeclarationType.Module)
59+
.Where(module => module != null)
60+
.SelectMany(module => DoGetInspectionResults(module.QualifiedModuleName, finder));
61+
}
62+
63+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
64+
{
65+
var finder = DeclarationFinderProvider.DeclarationFinder;
66+
return DoGetInspectionResults(module, finder);
67+
}
68+
69+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
70+
{
71+
var userDeclarations = finder.Members(module).ToList();
72+
var identifierReferences = finder.IdentifierReferences(module).ToList();
73+
var annotations = _state.GetAnnotations(module);
5974

6075
var unboundAnnotations = UnboundAnnotations(annotations, userDeclarations, identifierReferences)
6176
.Where(annotation => !annotation.Annotation.Target.HasFlag(AnnotationTarget.General)
6277
|| annotation.AnnotatedLine == null);
63-
var attributeAnnotationsInDocuments = AttributeAnnotationsInDocuments(userDeclarations);
6478

6579
var attributeAnnotationsOnDeclarationsNotAllowingAttributes = AttributeAnnotationsOnDeclarationsNotAllowingAttributes(userDeclarations);
6680

6781
var illegalAnnotations = unboundAnnotations
68-
.Concat(attributeAnnotationsInDocuments)
6982
.Concat(attributeAnnotationsOnDeclarationsNotAllowingAttributes)
70-
.ToHashSet();
83+
.Distinct();
84+
85+
if (module.ComponentType == ComponentType.Document)
86+
{
87+
var attributeAnnotationsInDocuments = AttributeAnnotationsInDocuments(userDeclarations);
88+
illegalAnnotations = illegalAnnotations
89+
.Concat(attributeAnnotationsInDocuments)
90+
.Distinct();
91+
}
7192

72-
return illegalAnnotations.Select(annotation =>
73-
new QualifiedContextInspectionResult(
74-
this,
75-
string.Format(InspectionResults.IllegalAnnotationInspection, annotation.Context.annotationName().GetText()),
76-
new QualifiedContext(annotation.QualifiedSelection.QualifiedName, annotation.Context)));
93+
return illegalAnnotations
94+
.Select(InspectionResult)
95+
.ToList();
96+
}
97+
98+
private IInspectionResult InspectionResult(IParseTreeAnnotation pta)
99+
{
100+
return new QualifiedContextInspectionResult(
101+
this,
102+
ResultDescription(pta),
103+
Context(pta));
104+
}
105+
106+
private static string ResultDescription(IParseTreeAnnotation pta)
107+
{
108+
var annotationText = pta.Context.annotationName().GetText();
109+
return string.Format(
110+
InspectionResults.IllegalAnnotationInspection,
111+
annotationText);
112+
}
113+
114+
private static QualifiedContext Context(IParseTreeAnnotation pta)
115+
{
116+
return new QualifiedContext(pta.QualifiedSelection.QualifiedName, pta.Context);
77117
}
78118

79119
private static IEnumerable<IParseTreeAnnotation> UnboundAnnotations(IEnumerable<IParseTreeAnnotation> annotations, IEnumerable<Declaration> userDeclarations, IEnumerable<IdentifierReference> identifierReferences)
@@ -91,7 +131,8 @@ private static IEnumerable<IParseTreeAnnotation> AttributeAnnotationsInDocuments
91131
{
92132
var declarationsInDocuments = userDeclarations
93133
.Where(declaration => declaration.QualifiedModuleName.ComponentType == ComponentType.Document);
94-
return declarationsInDocuments.SelectMany(doc => doc.Annotations).Where(pta => pta.Annotation is IAttributeAnnotation);
134+
return declarationsInDocuments.SelectMany(doc => doc.Annotations)
135+
.Where(pta => pta.Annotation is IAttributeAnnotation);
95136
}
96137

97138
private static IEnumerable<IParseTreeAnnotation> AttributeAnnotationsOnDeclarationsNotAllowingAttributes(IEnumerable<Declaration> userDeclarations)

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -33,8 +33,13 @@ namespace Rubberduck.Inspections.Concrete
3333
/// </example>
3434
public sealed class MissingAnnotationArgumentInspection : ParseTreeInspectionBase
3535
{
36+
private readonly RubberduckParserState _state;
37+
3638
public MissingAnnotationArgumentInspection(RubberduckParserState state)
37-
: base(state) { }
39+
: base(state)
40+
{
41+
_state = state;
42+
}
3843

3944
public override CodeKind TargetKindOfCode => CodeKind.AttributesCode;
4045

Rubberduck.Parsing/Annotations/AnnotationBase.cs

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,5 @@
1-
using System;
2-
using System.Collections.Generic;
1+
using System.Collections.Generic;
32
using System.Linq;
4-
using Rubberduck.Parsing.Grammar;
5-
using Rubberduck.VBEditor;
63

74
namespace Rubberduck.Parsing.Annotations
85
{
@@ -12,7 +9,7 @@ public abstract class AnnotationBase : IAnnotation
129
public string Name { get; }
1310
public AnnotationTarget Target { get; }
1411

15-
public AnnotationBase(string name, AnnotationTarget target, bool allowMultiple = false)
12+
protected AnnotationBase(string name, AnnotationTarget target, bool allowMultiple = false)
1613
{
1714
Name = name;
1815
Target = target;

Rubberduck.Parsing/Annotations/IAnnotation.cs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,4 @@
1-
using Rubberduck.Parsing.Grammar;
2-
using Rubberduck.VBEditor;
3-
using System;
1+
using System;
42
using System.Collections.Generic;
53

64
namespace Rubberduck.Parsing.Annotations

Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -139,7 +139,7 @@ protected void ResolveDeclarations(QualifiedModuleName module, IParseTree tree,
139139
}
140140
Logger.Debug($"Creating declarations for module {module.Name}.");
141141

142-
var annotationsOnWhiteSpaceLines = _state.GetModuleAnnotations(module)
142+
var annotationsOnWhiteSpaceLines = _state.GetAnnotations(module)
143143
.Where(a => a.AnnotatedLine.HasValue)
144144
.GroupBy(a => a.AnnotatedLine.Value)
145145
.ToDictionary();

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -687,7 +687,7 @@ public List<IParseTreeAnnotation> AllAnnotations
687687
}
688688
}
689689

690-
public IEnumerable<IParseTreeAnnotation> GetModuleAnnotations(QualifiedModuleName module)
690+
public IEnumerable<IParseTreeAnnotation> GetAnnotations(QualifiedModuleName module)
691691
{
692692
if (_moduleStates.TryGetValue(module, out var result))
693693
{

0 commit comments

Comments
 (0)