Skip to content

Commit 2774943

Browse files
authored
Merge pull request #5166 from MDoerner/DefaultMemberAccessInspections
Default member access inspections
2 parents f9140b5 + a9f04f8 commit 2774943

File tree

39 files changed

+2247
-320
lines changed

39 files changed

+2247
-320
lines changed
Lines changed: 72 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,72 @@
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.Inspections;
7+
8+
namespace Rubberduck.Inspections.Concrete
9+
{
10+
/// <summary>
11+
/// Identifies the use of non-indexed default member accesses.
12+
/// </summary>
13+
/// <why>
14+
/// Default member accesses hide away the actually called member. This is especially misleading if there is no indication in the expression that such a call is made
15+
/// and can cause errors in which a member was forgotten to be called to go unnoticed.
16+
/// </why>
17+
/// <example hasResult="true">
18+
/// <![CDATA[
19+
/// Public Sub DoSomething(ByVal arg As ADODB.Field)
20+
/// Dim bar As Variant
21+
/// bar = arg
22+
/// End Sub
23+
/// ]]>
24+
/// </example>
25+
/// <example hasResult="true">
26+
/// <![CDATA[
27+
/// Public Sub DoSomething(ByVal arg As ADODB.Connection)
28+
/// Dim bar As String
29+
/// arg = bar
30+
/// End Sub
31+
/// ]]>
32+
/// </example>
33+
/// <example hasResult="false">
34+
/// <![CDATA[
35+
/// Public Sub DoSomething(ByVal arg As ADODB.Field)
36+
/// Dim bar As Variant
37+
/// bar = arg.Value
38+
/// End Sub
39+
/// ]]>
40+
/// </example>
41+
/// <example hasResult="false">
42+
/// <![CDATA[
43+
/// Public Sub DoSomething(ByVal arg As ADODB.Connection)
44+
/// Dim bar As String
45+
/// arg.ConnectionString = bar
46+
/// End Sub
47+
/// ]]>
48+
public sealed class ImplicitDefaultMemberAccessInspection : IdentifierReferenceInspectionBase
49+
{
50+
public ImplicitDefaultMemberAccessInspection(RubberduckParserState state)
51+
: base(state)
52+
{
53+
Severity = CodeInspectionSeverity.Suggestion;
54+
}
55+
56+
protected override bool IsResultReference(IdentifierReference reference)
57+
{
58+
return reference.IsNonIndexedDefaultMemberAccess
59+
&& reference.DefaultMemberRecursionDepth == 1
60+
&& !reference.IsProcedureCoercion
61+
&& !reference.IsInnerRecursiveDefaultMemberAccess
62+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
63+
}
64+
65+
protected override string ResultDescription(IdentifierReference reference)
66+
{
67+
var expression = reference.IdentifierName;
68+
var defaultMember = reference.Declaration.QualifiedName.ToString();
69+
return string.Format(InspectionResults.ImplicitDefaultMemberAccessInspection, expression, defaultMember);
70+
}
71+
}
72+
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAssignmentInspection.cs

Lines changed: 0 additions & 77 deletions
This file was deleted.
Lines changed: 93 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,93 @@
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.Inspections;
7+
8+
namespace Rubberduck.Inspections.Concrete
9+
{
10+
/// <summary>
11+
/// Identifies the use of indexed default member accesses that require a recursive default member resolution.
12+
/// </summary>
13+
/// <why>
14+
/// Default member accesses hide away the actually called member. This is especially misleading if there is no indication in the expression that such a call is made
15+
/// and the final default member is not on the interface of the object itself. In particular, this can cause errors in which a member was forgotten to be called to go unnoticed.
16+
/// </why>
17+
/// <example hasResult="true">
18+
/// <module name="Class1" type="Class Module">
19+
/// <![CDATA[
20+
/// Public Function Foo() As Class2
21+
/// Attibute Foo.VB_UserMemId = 0
22+
/// Set Foo = New Class2
23+
/// End Function
24+
/// ]]>
25+
/// </module>
26+
/// <module name="Class2" type="Class Module">
27+
/// <![CDATA[
28+
/// Public Function Bar() As Long
29+
/// Attibute Bar.VB_UserMemId = 0
30+
/// Foo = 42
31+
/// End Function
32+
/// ]]>
33+
/// </module>
34+
/// <module name="Module" type="Standard Module">
35+
/// <![CDATA[
36+
/// Public Sub DoSomething(ByVal arg As Class1)
37+
/// Dim bar As Variant
38+
/// bar = arg
39+
/// End Sub
40+
/// ]]>
41+
/// </module>
42+
/// </example>
43+
/// <example hasResult="false">
44+
/// <module name="Class1" type="Class Module">
45+
/// <![CDATA[
46+
/// Public Function Foo() As Class2
47+
/// Attibute Foo.VB_UserMemId = 0
48+
/// Set Foo = New Class2
49+
/// End Function
50+
/// ]]>
51+
/// </module>
52+
/// <module name="Class2" type="Class Module">
53+
/// <![CDATA[
54+
/// Public Function Bar() As Long
55+
/// Attibute Bar.VB_UserMemId = 0
56+
/// Foo = 42
57+
/// End Function
58+
/// ]]>
59+
/// </module>
60+
/// <module name="Module" type="Standard Module">
61+
/// <![CDATA[
62+
/// Public Sub DoSomething(ByVal arg As Class1)
63+
/// Dim bar As Variant
64+
/// bar = arg.Foo().Bar()
65+
/// End Sub
66+
/// ]]>
67+
/// </module>
68+
/// </example>
69+
public sealed class ImplicitRecursiveDefaultMemberAccessInspection : IdentifierReferenceInspectionBase
70+
{
71+
public ImplicitRecursiveDefaultMemberAccessInspection(RubberduckParserState state)
72+
: base(state)
73+
{
74+
Severity = CodeInspectionSeverity.Suggestion;
75+
}
76+
77+
protected override bool IsResultReference(IdentifierReference reference)
78+
{
79+
return reference.IsNonIndexedDefaultMemberAccess
80+
&& reference.DefaultMemberRecursionDepth > 1
81+
&& !reference.IsProcedureCoercion
82+
&& !reference.IsInnerRecursiveDefaultMemberAccess
83+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
84+
}
85+
86+
protected override string ResultDescription(IdentifierReference reference)
87+
{
88+
var expression = reference.IdentifierName;
89+
var defaultMember = reference.Declaration.QualifiedName.ToString();
90+
return string.Format(InspectionResults.ImplicitRecursiveDefaultMemberAccessInspection, expression, defaultMember);
91+
}
92+
}
93+
}
Lines changed: 77 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,77 @@
1+
using System.Collections.Generic;
2+
using Rubberduck.Inspections.Abstract;
3+
using Rubberduck.Resources.Inspections;
4+
using Rubberduck.Parsing.Symbols;
5+
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.Inspections.Inspections.Extensions;
7+
using Rubberduck.Parsing.Inspections;
8+
using Rubberduck.VBEditor;
9+
10+
namespace Rubberduck.Inspections.Concrete
11+
{
12+
/// <summary>
13+
/// Identifies the use of indexed default member accesses for which the default member cannot be determined at compile time.
14+
/// </summary>
15+
/// <why>
16+
/// Default member accesses hide away the actually called member. This is especially misleading if there is no indication in the expression that such a call is made
17+
/// and if the default member cannot be determined from the declared type of the object. As a consequence, errors in which a member was forgotten to be called can go unnoticed
18+
/// and should there not be a suitable default member at runtime, an error 438 'Object doesn't support this property or method' will be raised.
19+
/// </why>
20+
/// <example hasResult="true">
21+
/// <![CDATA[
22+
/// Public Sub DoSomething(ByVal arg As Object)
23+
/// Dim bar As Variant
24+
/// bar = arg
25+
/// End Sub
26+
/// ]]>
27+
/// <example hasResult="true">
28+
/// <![CDATA[
29+
/// Public Sub DoSomething(ByVal arg As Object)
30+
/// Dim bar As Variant
31+
/// arg = bar
32+
/// End Sub
33+
/// ]]>
34+
/// </example>
35+
/// <example hasResult="false">
36+
/// <![CDATA[
37+
/// Public Sub DoSomething(ByVal arg As Object)
38+
/// Dim bar As Variant
39+
/// bar = arg.SomeValueReturningMember
40+
/// End Sub
41+
/// ]]>
42+
/// <example hasResult="false">
43+
/// <![CDATA[
44+
/// Public Sub DoSomething(ByVal arg As Object)
45+
/// Dim bar As Variant
46+
/// arg.SomePropertyLet = bar
47+
/// End Sub
48+
/// ]]>
49+
/// </example>
50+
public sealed class ImplicitUnboundDefaultMemberAccessInspection : IdentifierReferenceInspectionBase
51+
{
52+
public ImplicitUnboundDefaultMemberAccessInspection(RubberduckParserState state)
53+
: base(state)
54+
{
55+
Severity = CodeInspectionSeverity.Warning;
56+
}
57+
58+
protected override IEnumerable<IdentifierReference> ReferencesInModule(QualifiedModuleName module)
59+
{
60+
return DeclarationFinderProvider.DeclarationFinder.UnboundDefaultMemberAccesses(module);
61+
}
62+
63+
protected override bool IsResultReference(IdentifierReference reference)
64+
{
65+
return reference.IsNonIndexedDefaultMemberAccess
66+
&& !reference.IsProcedureCoercion
67+
&& !reference.IsInnerRecursiveDefaultMemberAccess
68+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
69+
}
70+
71+
protected override string ResultDescription(IdentifierReference reference)
72+
{
73+
var expression = reference.IdentifierName;
74+
return string.Format(InspectionResults.ImplicitUnboundDefaultMemberAccessInspection, expression);
75+
}
76+
}
77+
}
Lines changed: 56 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,56 @@
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 indexed default member accesses.
13+
/// </summary>
14+
/// <why>
15+
/// An indexed default member access hides away the actually called member.
16+
/// </why>
17+
/// <example hasResult="true">
18+
/// <![CDATA[
19+
/// Public Sub DoSomething(ByVal coll As Collection)
20+
/// Dim bar As Variant
21+
/// bar = coll(23)
22+
/// End Sub
23+
/// ]]>
24+
/// </example>
25+
/// <example hasResult="false">
26+
/// <![CDATA[
27+
/// Public Sub DoSomething(ByVal coll As Collection)
28+
/// Dim bar As Variant
29+
/// bar = coll.Item(23)
30+
/// End Sub
31+
/// ]]>
32+
/// </example>
33+
public sealed class IndexedDefaultMemberAccessInspection : IdentifierReferenceInspectionBase
34+
{
35+
public IndexedDefaultMemberAccessInspection(RubberduckParserState state)
36+
: base(state)
37+
{
38+
Severity = CodeInspectionSeverity.Hint;
39+
}
40+
41+
protected override bool IsResultReference(IdentifierReference reference)
42+
{
43+
return reference.IsIndexedDefaultMemberAccess
44+
&& reference.DefaultMemberRecursionDepth == 1
45+
&& !(reference.Context is VBAParser.DictionaryAccessContext)
46+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
47+
}
48+
49+
protected override string ResultDescription(IdentifierReference reference)
50+
{
51+
var expression = reference.IdentifierName;
52+
var defaultMember = reference.Declaration.QualifiedName.ToString();
53+
return string.Format(InspectionResults.IndexedDefaultMemberAccessInspection, expression, defaultMember);
54+
}
55+
}
56+
}

0 commit comments

Comments
 (0)