Skip to content

Commit 0c4bb18

Browse files
authored
Merge pull request #5347 from MDoerner/LetReferenceInspectionsUseBaseClass
Let reference inspections use base class
2 parents 5cc81de + bd58d29 commit 0c4bb18

File tree

55 files changed

+1423
-813
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

55 files changed

+1423
-813
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
}
Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,39 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Parsing.Symbols;
5+
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.Parsing.VBA.DeclarationCaching;
7+
8+
namespace Rubberduck.Inspections.Inspections.Abstract
9+
{
10+
public abstract class ArgumentReferenceInspectionFromDeclarationsBase : IdentifierReferenceInspectionFromDeclarationsBase
11+
{
12+
protected ArgumentReferenceInspectionFromDeclarationsBase(RubberduckParserState state)
13+
: base(state) { }
14+
15+
protected abstract bool IsUnsuitableArgument(ArgumentReference reference, DeclarationFinder finder);
16+
17+
protected virtual (bool isResult, object properties) IsUnsuitableArgumentWithAdditionalProperties(ArgumentReference reference, DeclarationFinder finder)
18+
{
19+
return (IsUnsuitableArgument(reference, finder), null);
20+
}
21+
22+
protected override IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
23+
{
24+
return ObjectionableDeclarations(finder)
25+
.OfType<ParameterDeclaration>()
26+
.SelectMany(parameter => parameter.ArgumentReferences);
27+
}
28+
29+
protected override (bool isResult, object properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
30+
{
31+
if (!(reference is ArgumentReference argumentReference))
32+
{
33+
return (false, null);
34+
}
35+
36+
return IsUnsuitableArgumentWithAdditionalProperties(argumentReference, finder);
37+
}
38+
}
39+
}

Rubberduck.CodeAnalysis/Inspections/Abstract/DeclarationInspectionBase.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,13 +10,11 @@ namespace Rubberduck.Inspections.Abstract
1010
{
1111
public abstract class DeclarationInspectionBase : InspectionBase
1212
{
13-
protected readonly IDeclarationFinderProvider DeclarationFinderProvider;
1413
protected readonly DeclarationType[] RelevantDeclarationTypes;
1514

1615
protected DeclarationInspectionBase(RubberduckParserState state, params DeclarationType[] relevantDeclarationTypes)
1716
: base(state)
1817
{
19-
DeclarationFinderProvider = state;
2018
RelevantDeclarationTypes = relevantDeclarationTypes;
2119
}
2220

Rubberduck.CodeAnalysis/Inspections/Abstract/IdentifierReferenceInspectionBase.cs

Lines changed: 30 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -4,25 +4,29 @@
44
using Rubberduck.Parsing.Inspections.Abstract;
55
using Rubberduck.Parsing.Symbols;
66
using Rubberduck.Parsing.VBA;
7+
using Rubberduck.Parsing.VBA.DeclarationCaching;
78
using Rubberduck.VBEditor;
89

910
namespace Rubberduck.Inspections.Abstract
1011
{
1112
public abstract class IdentifierReferenceInspectionBase : InspectionBase
1213
{
13-
protected readonly IDeclarationFinderProvider DeclarationFinderProvider;
14-
1514
protected IdentifierReferenceInspectionBase(RubberduckParserState state)
1615
: base(state)
16+
{}
17+
18+
protected abstract bool IsResultReference(IdentifierReference reference, DeclarationFinder finder);
19+
protected abstract string ResultDescription(IdentifierReference reference, dynamic properties = null);
20+
21+
protected virtual (bool isResult, object properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
1722
{
18-
DeclarationFinderProvider = state;
23+
return (IsResultReference(reference, finder), null);
1924
}
2025

21-
protected abstract bool IsResultReference(IdentifierReference reference);
22-
protected abstract string ResultDescription(IdentifierReference reference);
23-
2426
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2527
{
28+
var finder = DeclarationFinderProvider.DeclarationFinder;
29+
2630
var results = new List<IInspectionResult>();
2731
foreach (var moduleDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Module))
2832
{
@@ -32,34 +36,43 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3236
}
3337

3438
var module = moduleDeclaration.QualifiedModuleName;
35-
results.AddRange(DoGetInspectionResults(module));
39+
results.AddRange(DoGetInspectionResults(module, finder));
3640
}
3741

3842
return results;
3943
}
4044

41-
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
45+
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
4246
{
43-
var objectionableReferences = ReferencesInModule(module)
44-
.Where(IsResultReference);
47+
var objectionableReferencesWithProperties = ReferencesInModule(module, finder)
48+
.Select(reference => (reference, IsResultReferenceWithAdditionalProperties(reference, finder)))
49+
.Where(tpl => tpl.Item2.isResult)
50+
.Select(tpl => (tpl.reference, tpl.Item2.properties));
4551

46-
return objectionableReferences
47-
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))
52+
return objectionableReferencesWithProperties
53+
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
4854
.ToList();
4955
}
5056

51-
protected virtual IEnumerable<IdentifierReference> ReferencesInModule(QualifiedModuleName module)
57+
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
58+
{
59+
var finder = DeclarationFinderProvider.DeclarationFinder;
60+
return DoGetInspectionResults(module, finder);
61+
}
62+
63+
protected virtual IEnumerable<IdentifierReference> ReferencesInModule(QualifiedModuleName module, DeclarationFinder finder)
5264
{
53-
return DeclarationFinderProvider.DeclarationFinder.IdentifierReferences(module);
65+
return finder.IdentifierReferences(module);
5466
}
5567

56-
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
68+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider, dynamic properties = null)
5769
{
5870
return new IdentifierReferenceInspectionResult(
5971
this,
60-
ResultDescription(reference),
72+
ResultDescription(reference, properties),
6173
declarationFinderProvider,
62-
reference);
74+
reference,
75+
properties);
6376
}
6477
}
6578
}
Lines changed: 74 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,74 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Results;
4+
using Rubberduck.Parsing.Inspections.Abstract;
5+
using Rubberduck.Parsing.Symbols;
6+
using Rubberduck.Parsing.VBA;
7+
using Rubberduck.Parsing.VBA.DeclarationCaching;
8+
using Rubberduck.VBEditor;
9+
10+
namespace Rubberduck.Inspections.Abstract
11+
{
12+
public abstract class IdentifierReferenceInspectionFromDeclarationsBase : InspectionBase
13+
{
14+
protected IdentifierReferenceInspectionFromDeclarationsBase(RubberduckParserState state)
15+
: base(state)
16+
{}
17+
18+
protected abstract IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder);
19+
protected abstract string ResultDescription(IdentifierReference reference, dynamic properties = null);
20+
21+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
22+
{
23+
var finder = DeclarationFinderProvider.DeclarationFinder;
24+
var objectionableReferences = ObjectionableReferences(finder);
25+
var resultReferences = ResultReferences(objectionableReferences, finder);
26+
return resultReferences
27+
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
28+
.ToList();
29+
}
30+
31+
private IEnumerable<(IdentifierReference reference, object properties)> ResultReferences(IEnumerable<IdentifierReference> potentialResultReferences, DeclarationFinder finder)
32+
{
33+
return potentialResultReferences
34+
.Select(reference => (reference, IsResultReferenceWithAdditionalProperties(reference, finder)))
35+
.Where(tpl => tpl.Item2.isResult)
36+
.Select(tpl => (tpl.reference, tpl.Item2.properties));
37+
}
38+
39+
protected virtual IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
40+
{
41+
var objectionableDeclarations = ObjectionableDeclarations(finder);
42+
return objectionableDeclarations
43+
.SelectMany(declaration => declaration.References);
44+
}
45+
46+
protected virtual bool IsResultReference(IdentifierReference reference, DeclarationFinder finder) => true;
47+
48+
protected virtual (bool isResult, object properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
49+
{
50+
return (IsResultReference(reference, finder), null);
51+
}
52+
53+
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
54+
{
55+
var finder = DeclarationFinderProvider.DeclarationFinder;
56+
var objectionableReferences = ObjectionableReferences(finder)
57+
.Where(reference => reference.QualifiedModuleName.Equals(module));
58+
var resultReferences = ResultReferences(objectionableReferences, finder);
59+
return resultReferences
60+
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
61+
.ToList();
62+
}
63+
64+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider, dynamic properties = null)
65+
{
66+
return new IdentifierReferenceInspectionResult(
67+
this,
68+
ResultDescription(reference, properties),
69+
declarationFinderProvider,
70+
reference,
71+
properties);
72+
}
73+
}
74+
}

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

0 commit comments

Comments
 (0)