Skip to content

Commit a44dd18

Browse files
authored
Merge pull request #5164 from MDoerner/UseOfBangInspection
Adding "use of bang notation" inspection
2 parents f7fb6bd + 4e988b3 commit a44dd18

29 files changed

+1664
-154
lines changed
Lines changed: 66 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,66 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Inspections.Extensions;
4+
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing.Inspections.Abstract;
6+
using Rubberduck.Parsing.Symbols;
7+
using Rubberduck.Parsing.VBA;
8+
using Rubberduck.VBEditor;
9+
10+
namespace Rubberduck.Inspections.Abstract
11+
{
12+
public abstract class IdentifierReferenceInspectionBase : InspectionBase
13+
{
14+
protected readonly IDeclarationFinderProvider DeclarationFinderProvider;
15+
16+
public IdentifierReferenceInspectionBase(RubberduckParserState state)
17+
: base(state)
18+
{
19+
DeclarationFinderProvider = state;
20+
}
21+
22+
protected abstract bool IsResultReference(IdentifierReference reference);
23+
protected abstract string ResultDescription(IdentifierReference reference);
24+
25+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
26+
{
27+
var results = new List<IInspectionResult>();
28+
foreach (var moduleDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Module))
29+
{
30+
if (moduleDeclaration == null || moduleDeclaration.IsIgnoringInspectionResultFor(AnnotationName))
31+
{
32+
continue;
33+
}
34+
35+
var module = moduleDeclaration.QualifiedModuleName;
36+
results.AddRange(DoGetInspectionResults(module));
37+
}
38+
39+
return results;
40+
}
41+
42+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
43+
{
44+
var objectionableReferences = ReferencesInModule(module)
45+
.Where(IsResultReference);
46+
47+
return objectionableReferences
48+
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))
49+
.ToList();
50+
}
51+
52+
protected virtual IEnumerable<IdentifierReference> ReferencesInModule(QualifiedModuleName module)
53+
{
54+
return DeclarationFinderProvider.DeclarationFinder.IdentifierReferences(module);
55+
}
56+
57+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
58+
{
59+
return new IdentifierReferenceInspectionResult(
60+
this,
61+
ResultDescription(reference),
62+
declarationFinderProvider,
63+
reference);
64+
}
65+
}
66+
}

Rubberduck.CodeAnalysis/Inspections/Concrete/DefaultMemberRequiredInspection.cs

Lines changed: 7 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,11 @@
11
using System.Collections.Generic;
2-
using System.Linq;
32
using Rubberduck.Inspections.Abstract;
43
using Rubberduck.Inspections.Inspections.Extensions;
5-
using Rubberduck.Inspections.Results;
64
using Rubberduck.Parsing.Inspections;
7-
using Rubberduck.Parsing.Inspections.Abstract;
85
using Rubberduck.Parsing.Symbols;
96
using Rubberduck.Parsing.VBA;
107
using Rubberduck.Resources.Inspections;
8+
using Rubberduck.VBEditor;
119

1210
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
1311
{
@@ -55,43 +53,26 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
5553
/// End Sub
5654
/// ]]>
5755
/// </example>
58-
public class DefaultMemberRequiredInspection : InspectionBase
56+
public class DefaultMemberRequiredInspection : IdentifierReferenceInspectionBase
5957
{
60-
private readonly IDeclarationFinderProvider _declarationFinderProvider;
61-
6258
public DefaultMemberRequiredInspection(RubberduckParserState state)
6359
: base(state)
6460
{
65-
_declarationFinderProvider = state;
66-
6761
//This will most likely cause a runtime error. The exceptions are rare and should be refactored or made explicit with an @Ignore annotation.
6862
Severity = CodeInspectionSeverity.Error;
6963
}
7064

71-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
72-
{
73-
var finder = _declarationFinderProvider.DeclarationFinder;
74-
75-
var failedIndexedDefaultMemberAccesses = finder.FailedIndexedDefaultMemberAccesses();
76-
return failedIndexedDefaultMemberAccesses
77-
.Where(failedIndexedDefaultMemberAccess => !IsIgnored(failedIndexedDefaultMemberAccess))
78-
.Select(failedIndexedDefaultMemberAccess => InspectionResult(failedIndexedDefaultMemberAccess, _declarationFinderProvider));
79-
}
80-
81-
private bool IsIgnored(IdentifierReference assignment)
65+
protected override IEnumerable<IdentifierReference> ReferencesInModule(QualifiedModuleName module)
8266
{
83-
return assignment.IsIgnoringInspectionResultFor(AnnotationName);
67+
return DeclarationFinderProvider.DeclarationFinder.FailedIndexedDefaultMemberAccesses(module);
8468
}
8569

86-
private IInspectionResult InspectionResult(IdentifierReference failedCoercion, IDeclarationFinderProvider declarationFinderProvider)
70+
protected override bool IsResultReference(IdentifierReference failedIndexedDefaultMemberAccess)
8771
{
88-
return new IdentifierReferenceInspectionResult(this,
89-
ResultDescription(failedCoercion),
90-
declarationFinderProvider,
91-
failedCoercion);
72+
return !failedIndexedDefaultMemberAccess.IsIgnoringInspectionResultFor(AnnotationName);
9273
}
9374

94-
private string ResultDescription(IdentifierReference failedIndexedDefaultMemberAccess)
75+
protected override string ResultDescription(IdentifierReference failedIndexedDefaultMemberAccess)
9576
{
9677
var expression = failedIndexedDefaultMemberAccess.IdentifierName;
9778
var typeName = failedIndexedDefaultMemberAccess.Declaration?.FullAsTypeName;

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureRequiredInspection.cs

Lines changed: 7 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,11 @@
11
using System.Collections.Generic;
2-
using System.Linq;
32
using Rubberduck.Inspections.Abstract;
43
using Rubberduck.Inspections.Inspections.Extensions;
5-
using Rubberduck.Inspections.Results;
64
using Rubberduck.Parsing.Inspections;
7-
using Rubberduck.Parsing.Inspections.Abstract;
85
using Rubberduck.Parsing.Symbols;
96
using Rubberduck.Parsing.VBA;
107
using Rubberduck.Resources.Inspections;
8+
using Rubberduck.VBEditor;
119

1210
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
1311
{
@@ -53,43 +51,26 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
5351
/// End Sub
5452
/// ]]>
5553
/// </example>
56-
public class ProcedureRequiredInspection : InspectionBase
54+
public class ProcedureRequiredInspection : IdentifierReferenceInspectionBase
5755
{
58-
private readonly IDeclarationFinderProvider _declarationFinderProvider;
59-
6056
public ProcedureRequiredInspection(RubberduckParserState state)
6157
: base(state)
6258
{
63-
_declarationFinderProvider = state;
64-
6559
//This will most likely cause a runtime error. The exceptions are rare and should be refactored or made explicit with an @Ignore annotation.
6660
Severity = CodeInspectionSeverity.Error;
6761
}
6862

69-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
70-
{
71-
var finder = _declarationFinderProvider.DeclarationFinder;
72-
73-
var failedProcedureCoercions = finder.FailedProcedureCoercions();
74-
return failedProcedureCoercions
75-
.Where(failedCoercion => !IsIgnored(failedCoercion))
76-
.Select(failedCoercion => InspectionResult(failedCoercion, _declarationFinderProvider));
77-
}
78-
79-
private bool IsIgnored(IdentifierReference assignment)
63+
protected override IEnumerable<IdentifierReference> ReferencesInModule(QualifiedModuleName module)
8064
{
81-
return assignment.IsIgnoringInspectionResultFor(AnnotationName);
65+
return DeclarationFinderProvider.DeclarationFinder.FailedProcedureCoercions(module);
8266
}
8367

84-
private IInspectionResult InspectionResult(IdentifierReference failedCoercion, IDeclarationFinderProvider declarationFinderProvider)
68+
protected override bool IsResultReference(IdentifierReference failedCoercion)
8569
{
86-
return new IdentifierReferenceInspectionResult(this,
87-
ResultDescription(failedCoercion),
88-
declarationFinderProvider,
89-
failedCoercion);
70+
return !failedCoercion.IsIgnoringInspectionResultFor(AnnotationName);
9071
}
9172

92-
private string ResultDescription(IdentifierReference failedCoercion)
73+
protected override string ResultDescription(IdentifierReference failedCoercion)
9374
{
9475
var expression = failedCoercion.IdentifierName;
9576
var typeName = failedCoercion.Declaration?.FullAsTypeName;
Lines changed: 78 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,78 @@
1+
using Rubberduck.Inspections.Abstract;
2+
using Rubberduck.Resources.Inspections;
3+
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.Inspections.Inspections.Extensions;
6+
using Rubberduck.Parsing.Grammar;
7+
using Rubberduck.Parsing.Inspections;
8+
9+
namespace Rubberduck.Inspections.Concrete
10+
{
11+
/// <summary>
12+
/// Identifies the use of bang notation, formally known as dictionary access expression.
13+
/// </summary>
14+
/// <why>
15+
/// A dictionary access expression looks like a strongly typed call, but it actually is a stringly typed access to the parameterized default member of the object.
16+
/// </why>
17+
/// <example hasResult="true">
18+
/// <![CDATA[
19+
/// Public Sub DoSomething(ByVal wkb As Excel.Workbook)
20+
/// wkb.Worksheets!MySheet.Range("A1").Value = 42
21+
/// End Sub
22+
/// ]]>
23+
/// </example>
24+
/// <example hasResult="true">
25+
/// <![CDATA[
26+
/// Public Sub DoSomething(ByVal wkb As Excel.Workbook)
27+
/// With wkb.Worksheets
28+
/// !MySheet.Range("A1").Value = 42
29+
/// End With
30+
/// End Sub
31+
/// ]]>
32+
/// </example>
33+
/// <example hasResult="false">
34+
/// <![CDATA[
35+
/// Public Sub DoSomething(ByVal wkb As Excel.Workbook)
36+
/// wkb.Worksheets("MySheet").Range("A1").Value = 42
37+
/// End Sub
38+
/// ]]>
39+
/// </example>
40+
/// <example hasResult="false">
41+
/// <![CDATA[
42+
/// Public Sub DoSomething(ByVal wkb As Excel.Workbook)
43+
/// wkb.Worksheets.Item("MySheet").Range("A1").Value = 42
44+
/// End Sub
45+
/// ]]>
46+
/// </example>
47+
/// <example hasResult="false">
48+
/// <![CDATA[
49+
/// Public Sub DoSomething(ByVal wkb As Excel.Workbook)
50+
/// With wkb.Worksheets
51+
/// .Item("MySheet").Range("A1").Value = 42
52+
/// End With
53+
/// End Sub
54+
/// ]]>
55+
/// </example>
56+
public sealed class UseOfBangNotationInspection : IdentifierReferenceInspectionBase
57+
{
58+
public UseOfBangNotationInspection(RubberduckParserState state)
59+
: base(state)
60+
{
61+
Severity = CodeInspectionSeverity.Suggestion;
62+
}
63+
64+
protected override bool IsResultReference(IdentifierReference reference)
65+
{
66+
return reference.IsIndexedDefaultMemberAccess
67+
&& reference.DefaultMemberRecursionDepth == 1
68+
&& reference.Context is VBAParser.DictionaryAccessContext
69+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
70+
}
71+
72+
protected override string ResultDescription(IdentifierReference reference)
73+
{
74+
var expression = reference.IdentifierName;
75+
return string.Format(InspectionResults.UseOfBangNotationInspection, expression);
76+
}
77+
}
78+
}
Lines changed: 86 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,86 @@
1+
using Rubberduck.Inspections.Abstract;
2+
using Rubberduck.Resources.Inspections;
3+
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.Inspections.Inspections.Extensions;
6+
using Rubberduck.Parsing.Grammar;
7+
using Rubberduck.Parsing.Inspections;
8+
9+
namespace Rubberduck.Inspections.Concrete
10+
{
11+
/// <summary>
12+
/// Identifies the use of bang notation, formally known as dictionary access expression, for which a recursive default member resolution is necessary.
13+
/// </summary>
14+
/// <why>
15+
/// A dictionary access expression looks like a strongly typed call, but it actually is a stringly typed access to the parameterized default member of the object.
16+
/// This is especially misleading if the parameterized default member is not on the object itself and can only be reached by calling the parameterless default member first.
17+
/// </why>
18+
/// <example hasResult="true">
19+
/// <![CDATA[
20+
/// Public Function MyName(ByVal rst As ADODB.Recordset) As Variant
21+
/// MyName = rst!Name.Value
22+
/// End Function
23+
/// ]]>
24+
/// </example>
25+
/// <example hasResult="true">
26+
/// <![CDATA[
27+
/// Public Function MyName(ByVal rst As ADODB.Recordset) As Variant
28+
/// With rst
29+
/// MyName = !Name.Value
30+
/// End With
31+
/// End Function
32+
/// ]]>
33+
/// </example>
34+
/// <example hasResult="false">
35+
/// <![CDATA[
36+
/// Public Function MyName(ByVal rst As ADODB.Recordset) As Variant
37+
/// MyName = rst.Fields.Item("Name").Value
38+
/// End Function
39+
/// ]]>
40+
/// </example>
41+
/// <example hasResult="false">
42+
/// <![CDATA[
43+
/// Public Function MyName(ByVal rst As ADODB.Recordset) As Variant
44+
/// MyName = rst("Name").Value
45+
/// End Function
46+
/// ]]>
47+
/// </example>
48+
/// <example hasResult="false">
49+
/// <![CDATA[
50+
/// Public Function MyName(ByVal rst As ADODB.Recordset) As Variant
51+
/// MyName = rst.Fields!Name.Value 'see "UseOfBangNotation" inspection
52+
/// End Function
53+
/// ]]>
54+
/// </example>
55+
/// <example hasResult="false">
56+
/// <![CDATA[
57+
/// Public Function MyName(ByVal rst As ADODB.Recordset) As Variant
58+
/// With rst
59+
/// MyName = .Fields.Item("Name").Value
60+
/// End With
61+
/// End Function
62+
/// ]]>
63+
/// </example>
64+
public sealed class UseOfRecursiveBangNotationInspection : IdentifierReferenceInspectionBase
65+
{
66+
public UseOfRecursiveBangNotationInspection(RubberduckParserState state)
67+
: base(state)
68+
{
69+
Severity = CodeInspectionSeverity.Suggestion;
70+
}
71+
72+
protected override bool IsResultReference(IdentifierReference reference)
73+
{
74+
return reference.IsIndexedDefaultMemberAccess
75+
&& reference.DefaultMemberRecursionDepth > 1
76+
&& reference.Context is VBAParser.DictionaryAccessContext
77+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
78+
}
79+
80+
protected override string ResultDescription(IdentifierReference reference)
81+
{
82+
var expression = reference.IdentifierName;
83+
return string.Format(InspectionResults.UseOfRecursiveBangNotationInspection, expression);
84+
}
85+
}
86+
}

0 commit comments

Comments
 (0)