Skip to content

Commit 8c2fae8

Browse files
committed
Make MissingAnnotationArguments use only the annotations
Also adds an overload of DeclarationFinder.FindAnnotations providing all annotations in a module. IllegalAnnotationInspection now uses this in favor of RubberduckParserState.GetAnnotations, which allows to remove the dependency on the state.
1 parent 9fed0b3 commit 8c2fae8

File tree

4 files changed

+68
-46
lines changed

4 files changed

+68
-46
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs

Lines changed: 4 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -43,13 +43,9 @@ namespace Rubberduck.Inspections.Concrete
4343
/// </example>
4444
public sealed class IllegalAnnotationInspection : InspectionBase
4545
{
46-
private readonly RubberduckParserState _state;
47-
48-
public IllegalAnnotationInspection(RubberduckParserState state)
49-
: base(state)
50-
{
51-
_state = state;
52-
}
46+
public IllegalAnnotationInspection(IDeclarationFinderProvider declarationFinderProvider)
47+
: base(declarationFinderProvider)
48+
{}
5349

5450
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5551
{
@@ -70,7 +66,7 @@ private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleNam
7066
{
7167
var userDeclarations = finder.Members(module).ToList();
7268
var identifierReferences = finder.IdentifierReferences(module).ToList();
73-
var annotations = _state.GetAnnotations(module);
69+
var annotations = finder.FindAnnotations(module);
7470

7571
var unboundAnnotations = UnboundAnnotations(annotations, userDeclarations, identifierReferences)
7672
.Where(annotation => !annotation.Annotation.Target.HasFlag(AnnotationTarget.General)
Lines changed: 44 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,15 @@
1-
using Antlr4.Runtime;
1+
using System.Collections.Generic;
2+
using System.Linq;
23
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Results;
35
using Rubberduck.Parsing;
4-
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.Parsing.Annotations;
57
using Rubberduck.Parsing.Inspections.Abstract;
8+
using Rubberduck.Parsing.Symbols;
69
using Rubberduck.Resources.Inspections;
710
using Rubberduck.Parsing.VBA;
8-
using Rubberduck.Parsing.VBA.Parsing;
11+
using Rubberduck.Parsing.VBA.DeclarationCaching;
12+
using Rubberduck.VBEditor;
913

1014
namespace Rubberduck.Inspections.Concrete
1115
{
@@ -31,48 +35,57 @@ namespace Rubberduck.Inspections.Concrete
3135
/// ' ...
3236
/// ]]>
3337
/// </example>
34-
public sealed class MissingAnnotationArgumentInspection : ParseTreeInspectionBase
38+
public sealed class MissingAnnotationArgumentInspection : InspectionBase
3539
{
36-
private readonly RubberduckParserState _state;
40+
public MissingAnnotationArgumentInspection(IDeclarationFinderProvider declarationFinderProvider)
41+
: base(declarationFinderProvider)
42+
{}
3743

38-
public MissingAnnotationArgumentInspection(RubberduckParserState state)
39-
: base(state)
44+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4045
{
41-
_state = state;
46+
var finder = DeclarationFinderProvider.DeclarationFinder;
47+
48+
return finder.UserDeclarations(DeclarationType.Module)
49+
.Where(module => module != null)
50+
.SelectMany(module => DoGetInspectionResults(module.QualifiedModuleName, finder))
51+
.ToList();
4252
}
4353

44-
public override CodeKind TargetKindOfCode => CodeKind.AttributesCode;
54+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
55+
{
56+
var finder = DeclarationFinderProvider.DeclarationFinder;
57+
return DoGetInspectionResults(module, finder);
58+
}
59+
60+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
61+
{
62+
var objectionableAnnotations = finder.FindAnnotations(module)
63+
.Where(IsResultAnnotation);
4564

46-
public override IInspectionListener Listener { get; } =
47-
new InvalidAnnotationStatementListener();
65+
return objectionableAnnotations
66+
.Select(InspectionResult)
67+
.ToList();
68+
}
4869

49-
protected override string ResultDescription(QualifiedContext<ParserRuleContext> context)
70+
private static bool IsResultAnnotation(IParseTreeAnnotation pta)
5071
{
51-
var expressionText = ((VBAParser.AnnotationContext) context.Context).annotationName().GetText();
52-
return string.Format(
53-
InspectionResults.MissingAnnotationArgumentInspection,
54-
expressionText);
72+
return pta.Annotation.RequiredArguments > pta.AnnotationArguments.Count;
5573
}
5674

57-
protected override bool IsResultContext(QualifiedContext<ParserRuleContext> context)
75+
private IInspectionResult InspectionResult(IParseTreeAnnotation pta)
5876
{
59-
// FIXME don't actually use listeners here, iterate the Annotations instead
60-
// FIXME don't maintain a separate list for annotations that require arguments, instead use AnnotationAttribute to store that information
61-
var annotationContext = (VBAParser.AnnotationContext) context.Context;
62-
return (annotationContext.annotationName().GetText() == "Ignore"
63-
|| annotationContext.annotationName().GetText() == "Folder")
64-
&& annotationContext.annotationArgList() == null;
77+
var qualifiedContext = new QualifiedContext(pta.QualifiedSelection.QualifiedName, pta.Context);
78+
return new QualifiedContextInspectionResult(
79+
this,
80+
ResultDescription(pta),
81+
qualifiedContext);
6582
}
6683

67-
public class InvalidAnnotationStatementListener : InspectionListenerBase
84+
private static string ResultDescription(IParseTreeAnnotation pta)
6885
{
69-
public override void ExitAnnotation(VBAParser.AnnotationContext context)
70-
{
71-
if (context.annotationName() != null)
72-
{
73-
SaveContext(context);
74-
}
75-
}
86+
return string.Format(
87+
InspectionResults.MissingAnnotationArgumentInspection,
88+
pta.Annotation.Name);
7689
}
7790
}
7891
}

Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -68,9 +68,9 @@ private void FixNonModule(IInspectionResult result, IRewriteSession rewriteSessi
6868
{
6969
var module = result.QualifiedSelection.QualifiedName;
7070
var lineToAnnotate = result.QualifiedSelection.Selection.StartLine;
71-
var existingIgnoreAnnotation = _state.DeclarationFinder.FindAnnotations(module, lineToAnnotate)
72-
.Where(pta => pta.Annotation is IgnoreAnnotation)
73-
.FirstOrDefault();
71+
var existingIgnoreAnnotation = _state.DeclarationFinder
72+
.FindAnnotations(module, lineToAnnotate)
73+
.FirstOrDefault(pta => pta.Annotation is IgnoreAnnotation);
7474

7575
var annotationInfo = new IgnoreAnnotation();
7676
if (existingIgnoreAnnotation != null)

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 17 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ public class DeclarationFinder
3131
private readonly ConcurrentDictionary<QualifiedModuleName, IMutableFailedResolutionStore> _newFailedResolutionStores;
3232
private readonly ConcurrentDictionary<(QualifiedMemberName memberName, DeclarationType declarationType), ConcurrentBag<Declaration>> _newUndeclared;
3333

34-
private IDictionary<(QualifiedModuleName module, int annotatedLine), List<IParseTreeAnnotation>> _annotations;
34+
private IDictionary<QualifiedModuleName,IDictionary<int, List<IParseTreeAnnotation>>> _annotations;
3535
private IDictionary<Declaration, List<ParameterDeclaration>> _parametersByParent;
3636
private IDictionary<DeclarationType, List<Declaration>> _userDeclarationsByType;
3737

@@ -97,8 +97,9 @@ private List<Action> CollectionConstructionActions(IReadOnlyList<Declaration> de
9797
{
9898
() =>
9999
_annotations = annotations
100-
.Where(a => a.AnnotatedLine.HasValue)
101-
.GroupBy(a => (a.QualifiedSelection.QualifiedName, a.AnnotatedLine.Value))
100+
.GroupBy(annotation => annotation.QualifiedSelection.QualifiedName)
101+
.SelectMany(grp1 => grp1.GroupBy(annotation => annotation.AnnotatedLine.GetValueOrDefault(-1)), (grp1, grp2) => (grp1, grp2))
102+
.GroupBy(tpl => tpl.grp1.Key, tpl => tpl.grp2)
102103
.ToDictionary(),
103104
() =>
104105
_declarations = declarations
@@ -518,11 +519,23 @@ public IEnumerable<Declaration> FindMemberMatches(Declaration parent, string mem
518519

519520
public IEnumerable<IParseTreeAnnotation> FindAnnotations(QualifiedModuleName module, int annotatedLine)
520521
{
521-
return _annotations.TryGetValue((module, annotatedLine), out var result)
522+
if(!_annotations.TryGetValue(module, out var annotationsByLineInModule))
523+
{
524+
return Enumerable.Empty<IParseTreeAnnotation>();
525+
}
526+
527+
return annotationsByLineInModule.TryGetValue(annotatedLine, out var result)
522528
? result
523529
: Enumerable.Empty<IParseTreeAnnotation>();
524530
}
525531

532+
public IEnumerable<IParseTreeAnnotation> FindAnnotations(QualifiedModuleName module)
533+
{
534+
return _annotations.TryGetValue(module, out var annotationsByLineInModule)
535+
? annotationsByLineInModule.AllValues()
536+
: Enumerable.Empty<IParseTreeAnnotation>();
537+
}
538+
526539
public IEnumerable<IParseTreeAnnotation> FindAnnotations(QualifiedModuleName module, int annotatedLine, Type annotationType)
527540
{
528541
return FindAnnotations(module, annotatedLine).Where(pta => pta.Annotation.GetType() == annotationType);

0 commit comments

Comments
 (0)