Skip to content

Commit 92efa31

Browse files
committed
Amend identifier reference inspection base classes to allow providing additional properties for results
Also moves more inspections to the base classes.
1 parent b15e618 commit 92efa31

10 files changed

+208
-133
lines changed
Lines changed: 43 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,43 @@
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 reference, object properties)> ObjectionableReferences(DeclarationFinder finder)
23+
{
24+
return ObjectionableDeclarations(finder)
25+
.OfType<ModuleBodyElementDeclaration>()
26+
.SelectMany(declaration => declaration.Parameters)
27+
.SelectMany(parameter => parameter.ArgumentReferences)
28+
.Select(reference => (reference, IsResultReferenceWithAdditionalProperties(reference, finder)))
29+
.Where(tpl => tpl.Item2.isResult)
30+
.Select(tpl => ((IdentifierReference) tpl.reference, tpl.Item2.properties)); ;
31+
}
32+
33+
protected override (bool isResult, object properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
34+
{
35+
if (!(reference is ArgumentReference argumentReference))
36+
{
37+
return (false, null);
38+
}
39+
40+
return IsUnsuitableArgumentWithAdditionalProperties(argumentReference, finder);
41+
}
42+
}
43+
}

Rubberduck.CodeAnalysis/Inspections/Abstract/IdentifierReferenceInspectionBase.cs

Lines changed: 14 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,11 @@ public IdentifierReferenceInspectionBase(RubberduckParserState state)
1818
protected abstract bool IsResultReference(IdentifierReference reference, DeclarationFinder finder);
1919
protected abstract string ResultDescription(IdentifierReference reference);
2020

21+
protected virtual (bool isResult, object properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
22+
{
23+
return (IsResultReference(reference, finder), null);
24+
}
25+
2126
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2227
{
2328
var finder = DeclarationFinderProvider.DeclarationFinder;
@@ -39,11 +44,13 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3944

4045
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
4146
{
42-
var objectionableReferences = ReferencesInModule(module, finder)
43-
.Where(reference => IsResultReference(reference, finder));
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));
4451

45-
return objectionableReferences
46-
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))
52+
return objectionableReferencesWithProperties
53+
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
4754
.ToList();
4855
}
4956

@@ -58,13 +65,14 @@ protected virtual IEnumerable<IdentifierReference> ReferencesInModule(QualifiedM
5865
return finder.IdentifierReferences(module);
5966
}
6067

61-
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
68+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider, dynamic properties = null)
6269
{
6370
return new IdentifierReferenceInspectionResult(
6471
this,
6572
ResultDescription(reference),
6673
declarationFinderProvider,
67-
reference);
74+
reference,
75+
properties);
6876
}
6977
}
7078
}

Rubberduck.CodeAnalysis/Inspections/Abstract/IdentifierReferenceInspectionFromDeclarationsBase.cs

Lines changed: 15 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -23,37 +23,45 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2323
var finder = DeclarationFinderProvider.DeclarationFinder;
2424
var objectionableReferences = ObjectionableReferences(finder);
2525
return objectionableReferences
26-
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))
26+
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
2727
.ToList();
2828
}
2929

30-
protected virtual IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
30+
protected virtual IEnumerable<(IdentifierReference reference, object properties)> ObjectionableReferences(DeclarationFinder finder)
3131
{
3232
var objectionableDeclarations = ObjectionableDeclarations(finder);
3333
return objectionableDeclarations
3434
.SelectMany(declaration => declaration.References)
35-
.Where(reference => IsResultReference(reference, finder));
35+
.Select(reference => (reference, IsResultReferenceWithAdditionalProperties(reference, finder)))
36+
.Where(tpl => tpl.Item2.isResult)
37+
.Select(tpl => (tpl.reference, tpl.Item2.properties));
3638
}
3739

3840
protected virtual bool IsResultReference(IdentifierReference reference, DeclarationFinder finder) => true;
3941

42+
protected virtual (bool isResult, object properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
43+
{
44+
return (IsResultReference(reference, finder), null);
45+
}
46+
4047
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
4148
{
4249
var finder = DeclarationFinderProvider.DeclarationFinder;
4350
var objectionableReferences = ObjectionableReferences(finder);
4451
return objectionableReferences
45-
.Where(reference => reference.QualifiedModuleName.Equals(module))
46-
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))
52+
.Where(tpl => tpl.reference.QualifiedModuleName.Equals(module))
53+
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
4754
.ToList();
4855
}
4956

50-
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
57+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider, dynamic properties = null)
5158
{
5259
return new IdentifierReferenceInspectionResult(
5360
this,
5461
ResultDescription(reference),
5562
declarationFinderProvider,
56-
reference);
63+
reference,
64+
properties);
5765
}
5866
}
5967
}

Rubberduck.CodeAnalysis/Inspections/Abstract/InspectionResultBase.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,8 @@
11
using System.Collections.Generic;
2-
using System.IO;
32
using Antlr4.Runtime;
43
using Rubberduck.Common;
54
using Rubberduck.Parsing.Inspections;
65
using Rubberduck.Parsing.Inspections.Abstract;
7-
using Rubberduck.Resources.Inspections;
86
using Rubberduck.Parsing.Symbols;
97
using Rubberduck.VBEditor;
108
using Rubberduck.Interaction.Navigation;

Rubberduck.CodeAnalysis/Inspections/Abstract/IsMissingInspectionBase.cs

Lines changed: 3 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -1,18 +1,14 @@
11
using System.Collections.Generic;
22
using System.Linq;
3-
using Antlr4.Runtime;
4-
using NLog;
5-
using Rubberduck.Inspections.Abstract;
63
using Rubberduck.Parsing;
7-
using Rubberduck.Parsing.Binding;
84
using Rubberduck.Parsing.Grammar;
95
using Rubberduck.Parsing.Symbols;
106
using Rubberduck.Parsing.VBA;
117
using Rubberduck.Parsing.VBA.DeclarationCaching;
128

139
namespace Rubberduck.Inspections.Inspections.Abstract
1410
{
15-
public abstract class IsMissingInspectionBase : IdentifierReferenceInspectionFromDeclarationsBase
11+
public abstract class IsMissingInspectionBase : ArgumentReferenceInspectionFromDeclarationsBase
1612
{
1713
protected IsMissingInspectionBase(RubberduckParserState state)
1814
: base(state) { }
@@ -23,9 +19,6 @@ protected IsMissingInspectionBase(RubberduckParserState state)
2319
"VBA6.DLL;VBA.Information.IsMissing"
2420
};
2521

26-
protected abstract bool IsUnsuitableArgument(ArgumentReference reference, DeclarationFinder finder);
27-
28-
2922
protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
3023
{
3124
return IsMissingDeclarations(finder);
@@ -34,7 +27,7 @@ protected override IEnumerable<Declaration> ObjectionableDeclarations(Declaratio
3427
protected IReadOnlyList<Declaration> IsMissingDeclarations(DeclarationFinder finder)
3528
{
3629
var vbaProjects = finder.Projects
37-
.Where(project => project.IdentifierName == "VBA")
30+
.Where(project => project.IdentifierName == "VBA" && !project.IsUserDefined)
3831
.ToList();
3932

4033
if (!vbaProjects.Any())
@@ -60,22 +53,7 @@ protected IReadOnlyList<Declaration> IsMissingDeclarations(DeclarationFinder fin
6053
return isMissing;
6154
}
6255

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));
70-
}
71-
72-
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
73-
{
74-
return reference is ArgumentReference argumentReference
75-
&& IsUnsuitableArgument(argumentReference, finder);
76-
}
77-
78-
protected ParameterDeclaration GetParameterForReference(ArgumentReference reference, DeclarationFinder finder)
56+
protected ParameterDeclaration ParameterForReference(ArgumentReference reference, DeclarationFinder finder)
7957
{
8058
var argumentContext = reference.Context as VBAParser.LExprContext;
8159
if (!(argumentContext?.lExpression() is VBAParser.SimpleNameExprContext name))

0 commit comments

Comments
 (0)