Skip to content

Commit b15e618

Browse files
committed
Add declaration finder as parameter to IsResultReference on inspection base class
Also moves further identifier reference inspections to the appropriate base classes.
1 parent 9584c57 commit b15e618

25 files changed

+435
-292
lines changed

Rubberduck.CodeAnalysis/CodePathAnalysis/Extensions/NodeExtensions.cs

Lines changed: 8 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -2,13 +2,12 @@
22
using System;
33
using System.Collections.Generic;
44
using System.Linq;
5-
using Rubberduck.Parsing.Symbols;
65

76
namespace Rubberduck.Inspections.CodePathAnalysis.Extensions
87
{
98
public static class NodeExtensions
109
{
11-
public static IEnumerable<INode> GetFlattenedNodes(this INode node, IEnumerable<Type> excludedTypes)
10+
public static IEnumerable<INode> FlattenedNodes(this INode node, IEnumerable<Type> excludedTypes)
1211
{
1312
foreach (var child in node.Children)
1413
{
@@ -18,15 +17,15 @@ public static IEnumerable<INode> GetFlattenedNodes(this INode node, IEnumerable<
1817
}
1918
else
2019
{
21-
foreach (var nextChild in GetFlattenedNodes(child, excludedTypes))
20+
foreach (var nextChild in FlattenedNodes(child, excludedTypes))
2221
{
2322
yield return nextChild;
2423
}
2524
}
2625
}
2726
}
2827

29-
public static IEnumerable<INode> GetNodes(this INode node, IEnumerable<Type> types)
28+
public static IEnumerable<INode> Nodes(this INode node, ICollection<Type> types)
3029
{
3130
if (types.Contains(node.GetType()))
3231
{
@@ -35,50 +34,26 @@ public static IEnumerable<INode> GetNodes(this INode node, IEnumerable<Type> typ
3534

3635
foreach (var child in node.Children)
3736
{
38-
foreach (var childNode in GetNodes(child, types))
37+
foreach (var childNode in Nodes(child, types))
3938
{
4039
yield return childNode;
4140
}
4241
}
4342
}
4443

45-
public static INode GetFirstNode(this INode node, IEnumerable<Type> excludedTypes)
44+
public static INode GetFirstNode(this INode node, ICollection<Type> excludedTypes)
4645
{
4746
if (!excludedTypes.Contains(node.GetType()))
4847
{
4948
return node;
5049
}
5150

52-
return GetFirstNode(node.Children[0], excludedTypes);
53-
}
54-
55-
public static List<IdentifierReference> GetIdentifierReferences(this INode node)
56-
{
57-
var nodes = new List<IdentifierReference>();
58-
59-
var blockNodes = node.GetNodes(new[] { typeof(BlockNode) });
60-
foreach (var block in blockNodes)
51+
if (!node.Children.Any())
6152
{
62-
INode lastNode = default;
63-
foreach (var flattenedNode in block.GetFlattenedNodes(new[] { typeof(GenericNode), typeof(BlockNode) }))
64-
{
65-
if (flattenedNode is AssignmentNode &&
66-
lastNode is AssignmentNode)
67-
{
68-
nodes.Add(lastNode.Reference);
69-
}
70-
71-
lastNode = flattenedNode;
72-
}
73-
74-
if (lastNode is AssignmentNode &&
75-
block.Children[0].GetFirstNode(new[] { typeof(GenericNode) }) is DeclarationNode)
76-
{
77-
nodes.Add(lastNode.Reference);
78-
}
53+
return null;
7954
}
8055

81-
return nodes;
56+
return GetFirstNode(node.Children[0], excludedTypes);
8257
}
8358
}
8459
}

Rubberduck.CodeAnalysis/Inspections/Abstract/IdentifierReferenceInspectionBase.cs

Lines changed: 3 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -11,15 +11,11 @@ namespace Rubberduck.Inspections.Abstract
1111
{
1212
public abstract class IdentifierReferenceInspectionBase : InspectionBase
1313
{
14-
protected readonly IDeclarationFinderProvider DeclarationFinderProvider;
15-
1614
public IdentifierReferenceInspectionBase(RubberduckParserState state)
1715
: base(state)
18-
{
19-
DeclarationFinderProvider = state;
20-
}
16+
{}
2117

22-
protected abstract bool IsResultReference(IdentifierReference reference);
18+
protected abstract bool IsResultReference(IdentifierReference reference, DeclarationFinder finder);
2319
protected abstract string ResultDescription(IdentifierReference reference);
2420

2521
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
@@ -44,7 +40,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4440
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
4541
{
4642
var objectionableReferences = ReferencesInModule(module, finder)
47-
.Where(IsResultReference);
43+
.Where(reference => IsResultReference(reference, finder));
4844

4945
return objectionableReferences
5046
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))

Rubberduck.CodeAnalysis/Inspections/Abstract/IdentifierReferenceInspectionFromDeclarationsBase.cs

Lines changed: 4 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -11,13 +11,9 @@ namespace Rubberduck.Inspections.Abstract
1111
{
1212
public abstract class IdentifierReferenceInspectionFromDeclarationsBase : InspectionBase
1313
{
14-
protected readonly IDeclarationFinderProvider DeclarationFinderProvider;
15-
1614
protected IdentifierReferenceInspectionFromDeclarationsBase(RubberduckParserState state)
1715
: base(state)
18-
{
19-
DeclarationFinderProvider = state;
20-
}
16+
{}
2117

2218
protected abstract IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder);
2319
protected abstract string ResultDescription(IdentifierReference reference);
@@ -31,15 +27,15 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3127
.ToList();
3228
}
3329

34-
private IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
30+
protected virtual IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
3531
{
3632
var objectionableDeclarations = ObjectionableDeclarations(finder);
3733
return objectionableDeclarations
3834
.SelectMany(declaration => declaration.References)
39-
.Where(IsResultReference);
35+
.Where(reference => IsResultReference(reference, finder));
4036
}
4137

42-
protected virtual bool IsResultReference(IdentifierReference reference) => true;
38+
protected virtual bool IsResultReference(IdentifierReference reference, DeclarationFinder finder) => true;
4339

4440
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
4541
{

Rubberduck.CodeAnalysis/Inspections/Abstract/InspectionBase.cs

Lines changed: 26 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -17,12 +17,16 @@ namespace Rubberduck.Inspections.Abstract
1717
public abstract class InspectionBase : IInspection
1818
{
1919
protected readonly RubberduckParserState State;
20+
protected readonly IDeclarationFinderProvider DeclarationFinderProvider;
2021

21-
private readonly ILogger _logger = LogManager.GetCurrentClassLogger();
22+
protected readonly ILogger Logger;
2223

2324
protected InspectionBase(RubberduckParserState state)
2425
{
26+
Logger = LogManager.GetLogger(GetType().FullName);
27+
2528
State = state;
29+
DeclarationFinderProvider = state;
2630
Name = GetType().Name;
2731
}
2832

@@ -66,33 +70,26 @@ protected InspectionBase(RubberduckParserState state)
6670
/// <summary>
6771
/// Gets all declarations in the parser state without an @Ignore annotation for this inspection.
6872
/// </summary>
69-
protected virtual IEnumerable<Declaration> Declarations
70-
{
71-
get { return State.AllDeclarations.Where(declaration => !declaration.IsIgnoringInspectionResultFor(AnnotationName)); }
72-
}
73+
protected virtual IEnumerable<Declaration> Declarations => DeclarationFinderProvider
74+
.DeclarationFinder
75+
.AllDeclarations
76+
.Where(declaration => !declaration.IsIgnoringInspectionResultFor(AnnotationName));
7377

7478
/// <summary>
7579
/// Gets all user declarations in the parser state without an @Ignore annotation for this inspection.
7680
/// </summary>
77-
protected virtual IEnumerable<Declaration> UserDeclarations
78-
{
79-
get { return State.AllUserDeclarations.Where(declaration => !declaration.IsIgnoringInspectionResultFor(AnnotationName)); }
80-
}
81+
protected virtual IEnumerable<Declaration> UserDeclarations => DeclarationFinderProvider
82+
.DeclarationFinder
83+
.AllUserDeclarations
84+
.Where(declaration => !declaration.IsIgnoringInspectionResultFor(AnnotationName));
8185

82-
protected virtual IEnumerable<Declaration> BuiltInDeclarations
83-
{
84-
get { return State.AllDeclarations.Where(declaration => !declaration.IsUserDefined); }
85-
}
86+
protected virtual IEnumerable<Declaration> BuiltInDeclarations => DeclarationFinderProvider
87+
.DeclarationFinder
88+
.AllBuiltInDeclarations;
8689

87-
public int CompareTo(IInspection other)
88-
{
89-
return string.Compare(InspectionType + Name, other.InspectionType + other.Name, StringComparison.Ordinal);
90-
}
90+
public int CompareTo(IInspection other) => string.Compare(InspectionType + Name, other.InspectionType + other.Name, StringComparison.Ordinal);
91+
public int CompareTo(object obj) => CompareTo(obj as IInspection);
9192

92-
public int CompareTo(object obj)
93-
{
94-
return CompareTo(obj as IInspection);
95-
}
9693
protected abstract IEnumerable<IInspectionResult> DoGetInspectionResults();
9794

9895
/// <summary>
@@ -102,14 +99,15 @@ public int CompareTo(object obj)
10299
/// <returns></returns>
103100
public IEnumerable<IInspectionResult> GetInspectionResults(CancellationToken token)
104101
{
105-
var _stopwatch = new Stopwatch();
106-
_stopwatch.Start();
107-
var declarationFinder = State.DeclarationFinder;
102+
var stopwatch = new Stopwatch();
103+
stopwatch.Start();
104+
var declarationFinder = DeclarationFinderProvider.DeclarationFinder;
108105
var result = DoGetInspectionResults()
109-
.Where(ir => !ir.IsIgnoringInspectionResult(declarationFinder));
110-
_stopwatch.Stop();
111-
_logger.Trace("Intercepted invocation of '{0}.{1}' returned {2} objects.", GetType().Name, nameof(DoGetInspectionResults), result.Count());
112-
_logger.Trace("Intercepted invocation of '{0}.{1}' ran for {2}ms", GetType().Name, nameof(DoGetInspectionResults), _stopwatch.ElapsedMilliseconds);
106+
.Where(ir => !ir.IsIgnoringInspectionResult(declarationFinder))
107+
.ToList();
108+
stopwatch.Stop();
109+
Logger.Trace("Intercepted invocation of '{0}.{1}' returned {2} objects.", GetType().Name, nameof(DoGetInspectionResults), result.Count);
110+
Logger.Trace("Intercepted invocation of '{0}.{1}' ran for {2}ms", GetType().Name, nameof(DoGetInspectionResults), stopwatch.ElapsedMilliseconds);
113111
return result;
114112
}
115113

Rubberduck.CodeAnalysis/Inspections/Abstract/IsMissingInspectionBase.cs

Lines changed: 55 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -4,16 +4,16 @@
44
using NLog;
55
using Rubberduck.Inspections.Abstract;
66
using Rubberduck.Parsing;
7+
using Rubberduck.Parsing.Binding;
78
using Rubberduck.Parsing.Grammar;
89
using Rubberduck.Parsing.Symbols;
910
using Rubberduck.Parsing.VBA;
11+
using Rubberduck.Parsing.VBA.DeclarationCaching;
1012

1113
namespace Rubberduck.Inspections.Inspections.Abstract
1214
{
13-
public abstract class IsMissingInspectionBase : InspectionBase
15+
public abstract class IsMissingInspectionBase : IdentifierReferenceInspectionFromDeclarationsBase
1416
{
15-
private readonly ILogger _logger = LogManager.GetCurrentClassLogger();
16-
1717
protected IsMissingInspectionBase(RubberduckParserState state)
1818
: base(state) { }
1919

@@ -23,39 +23,72 @@ protected IsMissingInspectionBase(RubberduckParserState state)
2323
"VBA6.DLL;VBA.Information.IsMissing"
2424
};
2525

26-
protected IReadOnlyList<Declaration> IsMissingDeclarations
26+
protected abstract bool IsUnsuitableArgument(ArgumentReference reference, DeclarationFinder finder);
27+
28+
29+
protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
30+
{
31+
return IsMissingDeclarations(finder);
32+
}
33+
34+
protected IReadOnlyList<Declaration> IsMissingDeclarations(DeclarationFinder finder)
2735
{
28-
get
36+
var vbaProjects = finder.Projects
37+
.Where(project => project.IdentifierName == "VBA")
38+
.ToList();
39+
40+
if (!vbaProjects.Any())
2941
{
30-
var isMissing = BuiltInDeclarations.Where(decl => IsMissingQualifiedNames.Contains(decl.QualifiedName.ToString())).ToList();
42+
return new List<Declaration>();
43+
}
3144

32-
if (isMissing.Count == 0)
33-
{
34-
_logger.Trace("No 'IsMissing' Declarations were found in IsMissingInspectionBase.");
35-
}
45+
var informationModules = vbaProjects
46+
.Select(project => finder.FindStdModule("Information", project, true))
47+
.OfType<ModuleDeclaration>()
48+
.ToList();
3649

37-
return isMissing;
50+
if (!informationModules.Any())
51+
{
52+
return new List<Declaration>();
3853
}
54+
55+
var isMissing = informationModules
56+
.SelectMany(module => module.Members)
57+
.Where(decl => IsMissingQualifiedNames.Contains(decl.QualifiedName.ToString()))
58+
.ToList();
59+
60+
return isMissing;
61+
}
62+
63+
protected override IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
64+
{
65+
return ObjectionableDeclarations(finder)
66+
.OfType<ModuleBodyElementDeclaration>()
67+
.SelectMany(declaration => declaration.Parameters)
68+
.SelectMany(parameter => parameter.ArgumentReferences)
69+
.Where(reference => IsResultReference(reference, finder));
3970
}
4071

41-
protected ParameterDeclaration GetParameterForReference(IdentifierReference reference)
72+
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
4273
{
43-
// First case is for unqualified use: IsMissing(foo)
44-
// Second case if for use as a member access: VBA.IsMissing(foo)
45-
var argument = ((ParserRuleContext)reference.Context.Parent).GetDescendent<VBAParser.ArgumentExpressionContext>() ??
46-
((ParserRuleContext)reference.Context.Parent.Parent).GetDescendent<VBAParser.ArgumentExpressionContext>();
74+
return reference is ArgumentReference argumentReference
75+
&& IsUnsuitableArgument(argumentReference, finder);
76+
}
4777

48-
var name = argument?.GetDescendent<VBAParser.SimpleNameExprContext>();
49-
if (name == null || name.Parent.Parent != argument)
78+
protected ParameterDeclaration GetParameterForReference(ArgumentReference reference, DeclarationFinder finder)
79+
{
80+
var argumentContext = reference.Context as VBAParser.LExprContext;
81+
if (!(argumentContext?.lExpression() is VBAParser.SimpleNameExprContext name))
5082
{
5183
return null;
5284
}
5385

5486
var procedure = reference.Context.GetAncestor<VBAParser.ModuleBodyElementContext>();
55-
return UserDeclarations.Where(decl => decl is ModuleBodyElementDeclaration)
56-
.Cast<ModuleBodyElementDeclaration>()
57-
.FirstOrDefault(decl => decl.Context.Parent == procedure)?
58-
.Parameters.FirstOrDefault(param => param.IdentifierName.Equals(name.GetText()));
87+
//TODO: revisit this once PR #5338 is merged.
88+
return finder.UserDeclarations(DeclarationType.Member)
89+
.OfType<ModuleBodyElementDeclaration>()
90+
.FirstOrDefault(decl => decl.Context.Parent == procedure)?.Parameters
91+
.FirstOrDefault(param => param.IdentifierName.Equals(name.GetText()));
5992
}
6093
}
6194
}

0 commit comments

Comments
 (0)