Skip to content

Commit b615cd6

Browse files
committed
Add inspections for implicit default member accesses
These do not cover procedure coercions, which are covered separately. In particular, we have ImplicitDefaultMemberAccessInspection for ordinary not parameterized ones, ImplicitRecursiveDefaultMemberAccessInspection for not parameterized ones that require a resolution via a chain of default members and ImplicitUnboundDefaultMemberAccessInspection for unbound not paramterized ones.
1 parent 1a031e1 commit b615cd6

22 files changed

+970
-25
lines changed
Lines changed: 106 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,106 @@
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 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+
/// Class1:
20+
///
21+
/// Public Function Foo() As Long
22+
/// Attibute Foo.VB_UserMemId = 0
23+
/// Foo = 42
24+
/// End Function
25+
///
26+
/// Module:
27+
///
28+
/// Public Sub DoSomething(ByVal arg As Class1)
29+
/// Dim bar As Variant
30+
/// bar = arg
31+
/// End Sub
32+
/// ]]>
33+
/// </example>
34+
/// <example hasResult="true">
35+
/// <![CDATA[
36+
/// Class1:
37+
///
38+
/// Public Property Let Foo(RHS As Long)
39+
/// Attibute Foo.VB_UserMemId = 0
40+
/// End Function
41+
///
42+
/// Module:
43+
///
44+
/// Public Sub DoSomething(ByVal arg As Class1)
45+
/// Dim bar As Variant
46+
/// arg = bar
47+
/// End Sub
48+
/// ]]>
49+
/// </example>
50+
/// <example hasResult="false">
51+
/// <![CDATA[
52+
/// Class1:
53+
///
54+
/// Public Function Foo() As Long
55+
/// Attibute Foo.VB_UserMemId = 0
56+
/// Foo = 42
57+
/// End Function
58+
///
59+
/// Module:
60+
///
61+
/// Public Sub DoSomething(ByVal arg As Class1)
62+
/// Dim bar As Variant
63+
/// bar = arg.Foo()
64+
/// End Sub
65+
/// ]]>
66+
/// </example>
67+
/// <example hasResult="false">
68+
/// <![CDATA[
69+
/// Class1:
70+
///
71+
/// Public Property Let Foo(RHS As Long)
72+
/// Attibute Foo.VB_UserMemId = 0
73+
/// End Function
74+
///
75+
/// Module:
76+
///
77+
/// Public Sub DoSomething(ByVal arg As Class1)
78+
/// Dim bar As Variant
79+
/// arg.Foo = bar
80+
/// End Sub
81+
/// ]]>
82+
public sealed class ImplicitDefaultMemberAccessInspection : IdentifierReferenceInspectionBase
83+
{
84+
public ImplicitDefaultMemberAccessInspection(RubberduckParserState state)
85+
: base(state)
86+
{
87+
Severity = CodeInspectionSeverity.Suggestion;
88+
}
89+
90+
protected override bool IsResultReference(IdentifierReference reference)
91+
{
92+
return reference.IsNonIndexedDefaultMemberAccess
93+
&& reference.DefaultMemberRecursionDepth == 1
94+
&& !reference.IsProcedureCoercion
95+
&& !reference.IsInnerRecursiveDefaultMemberAccess
96+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
97+
}
98+
99+
protected override string ResultDescription(IdentifierReference reference)
100+
{
101+
var expression = reference.IdentifierName;
102+
var defaultMember = reference.Declaration.QualifiedName.ToString();
103+
return string.Format(InspectionResults.ImplicitDefaultMemberAccessInspection, expression, defaultMember);
104+
}
105+
}
106+
}
Lines changed: 89 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,89 @@
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 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+
/// <![CDATA[
19+
/// Class1:
20+
///
21+
/// Public Function Foo() As Class2
22+
/// Attibute Foo.VB_UserMemId = 0
23+
/// Set Foo = New Class2
24+
/// End Function
25+
///
26+
/// Class2:
27+
///
28+
/// Public Function Bar() As Long
29+
/// Attibute Bar.VB_UserMemId = 0
30+
/// Foo = 42
31+
/// End Function
32+
///
33+
/// Module:
34+
///
35+
/// Public Sub DoSomething(ByVal arg As Class1)
36+
/// Dim bar As Variant
37+
/// bar = arg
38+
/// End Sub
39+
/// ]]>
40+
/// </example>
41+
/// <example hasResult="false">
42+
/// <![CDATA[
43+
/// Class1:
44+
///
45+
/// Public Function Foo() As Class2
46+
/// Attibute Foo.VB_UserMemId = 0
47+
/// Set Foo = New Class2
48+
/// End Function
49+
///
50+
/// Class2:
51+
///
52+
/// Public Function Bar() As Long
53+
/// Attibute Bar.VB_UserMemId = 0
54+
/// Foo = 42
55+
/// End Function
56+
///
57+
/// Module:
58+
///
59+
/// Public Sub DoSomething(ByVal arg As Class1)
60+
/// Dim bar As Variant
61+
/// bar = arg.Foo().Bar()
62+
/// End Sub
63+
/// ]]>
64+
/// </example>
65+
public sealed class ImplicitRecursiveDefaultMemberAccessInspection : IdentifierReferenceInspectionBase
66+
{
67+
public ImplicitRecursiveDefaultMemberAccessInspection(RubberduckParserState state)
68+
: base(state)
69+
{
70+
Severity = CodeInspectionSeverity.Suggestion;
71+
}
72+
73+
protected override bool IsResultReference(IdentifierReference reference)
74+
{
75+
return reference.IsNonIndexedDefaultMemberAccess
76+
&& reference.DefaultMemberRecursionDepth > 1
77+
&& !reference.IsProcedureCoercion
78+
&& !reference.IsInnerRecursiveDefaultMemberAccess
79+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
80+
}
81+
82+
protected override string ResultDescription(IdentifierReference reference)
83+
{
84+
var expression = reference.IdentifierName;
85+
var defaultMember = reference.Declaration.QualifiedName.ToString();
86+
return string.Format(InspectionResults.ImplicitRecursiveDefaultMemberAccessInspection, expression, defaultMember);
87+
}
88+
}
89+
}
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 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+
}

Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedDefaultMemberAccessInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ namespace Rubberduck.Inspections.Concrete
1919
/// Class1:
2020
///
2121
/// Public Function Foo(ByVal arg As Long) As Long
22-
/// Attibute VB_UserMemId = 0
22+
/// Attibute Foo.VB_UserMemId = 0
2323
/// Foo = 42
2424
/// End Function
2525
///
@@ -36,7 +36,7 @@ namespace Rubberduck.Inspections.Concrete
3636
/// Class1:
3737
///
3838
/// Public Function Foo(ByVal arg As Long) As Long
39-
/// Attibute VB_UserMemId = 0
39+
/// Attibute Foo.VB_UserMemId = 0
4040
/// Foo = 42
4141
/// End Function
4242
///

Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedRecursiveDefaultMemberAccessInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,15 +16,15 @@ namespace Rubberduck.Inspections.Concrete
1616
/// </why>
1717
/// <example hasResult="true">
1818
/// <![CDATA[
19-
/// Public Sub DoSomething(ByVal arg As ADODB.Recordset)
19+
/// Public Sub DoSomething(ByVal rst As ADODB.Recordset)
2020
/// Dim bar As Variant
2121
/// bar = rst("MyField")
2222
/// End Sub
2323
/// ]]>
2424
/// </example>
2525
/// <example hasResult="false">
2626
/// <![CDATA[
27-
/// Public Sub DoSomething(ByVal arg As ADODB.Recordset)
27+
/// Public Sub DoSomething(ByVal rst As ADODB.Recordset)
2828
/// Dim bar As Variant
2929
/// bar = rst.Fields.Item("MyField")
3030
/// End Sub

Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedUnboundDefaultMemberAccessInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -19,15 +19,15 @@ namespace Rubberduck.Inspections.Concrete
1919
/// </why>
2020
/// <example hasResult="true">
2121
/// <![CDATA[
22-
/// Public Sub DoSomething(ByVal arg As Object)
22+
/// Public Sub DoSomething(ByVal rst As Object)
2323
/// Dim bar As Variant
2424
/// bar = rst("MyField")
2525
/// End Sub
2626
/// ]]>
2727
/// </example>
2828
/// <example hasResult="false">
2929
/// <![CDATA[
30-
/// Public Sub DoSomething(ByVal arg As Object)
30+
/// Public Sub DoSomething(ByVal rst As Object)
3131
/// Dim bar As Variant
3232
/// bar = rst.Fields.Item("MyField")
3333
/// End Sub

Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectWhereProcedureIsRequiredInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ namespace Rubberduck.Inspections.Concrete
2424
/// <module name="Class1" type="Class Module">
2525
/// <![CDATA[
2626
/// Public Function Foo() As Long
27-
/// Attibute VB_UserMemId = 0
27+
/// Attibute Foo.VB_UserMemId = 0
2828
/// Foo = 42
2929
/// End Function
3030
/// ]]>
@@ -41,7 +41,7 @@ namespace Rubberduck.Inspections.Concrete
4141
/// <module name="Class1" type="Class Module">
4242
/// <![CDATA[
4343
/// Public Function Foo() As Long
44-
/// Attibute VB_UserMemId = 0
44+
/// Attibute Foo.VB_UserMemId = 0
4545
/// Foo = 42
4646
/// End Function
4747
/// ]]>

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -367,7 +367,8 @@ public void AddReference(
367367
bool isNonIndexedDefaultMemberAccess = false,
368368
int defaultMemberRecursionDepth = 0,
369369
bool isArrayAccess = false,
370-
bool isProcedureCoercion = false
370+
bool isProcedureCoercion = false,
371+
bool isInnerRecursiveDefaultMemberAccess = false
371372
)
372373
{
373374
var oldReference = _references.FirstOrDefault(r =>
@@ -399,7 +400,8 @@ public void AddReference(
399400
isNonIndexedDefaultMemberAccess,
400401
defaultMemberRecursionDepth,
401402
isArrayAccess,
402-
isProcedureCoercion);
403+
isProcedureCoercion,
404+
isInnerRecursiveDefaultMemberAccess);
403405
_references.AddOrUpdate(newReference, 1, (key, value) => 1);
404406
}
405407

Rubberduck.Parsing/Symbols/IdentifierReference.cs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,8 @@ public IdentifierReference(
2828
bool isNonIndexedDefaultMemberAccess = false,
2929
int defaultMemberRecursionDepth = 0,
3030
bool isArrayAccess = false,
31-
bool isProcedureCoercion = false)
31+
bool isProcedureCoercion = false,
32+
bool isInnerRecursiveDefaultMemberAccess = false)
3233
{
3334
ParentScoping = parentScopingDeclaration;
3435
ParentNonScoping = parentNonScopingDeclaration;
@@ -46,6 +47,7 @@ public IdentifierReference(
4647
IsArrayAccess = isArrayAccess;
4748
IsProcedureCoercion = isProcedureCoercion;
4849
Annotations = annotations ?? new List<IParseTreeAnnotation>();
50+
IsInnerRecursiveDefaultMemberAccess = isInnerRecursiveDefaultMemberAccess;
4951
}
5052

5153
public QualifiedModuleName QualifiedModuleName { get; }
@@ -74,6 +76,7 @@ public IdentifierReference(
7476
public bool IsNonIndexedDefaultMemberAccess { get; }
7577
public bool IsDefaultMemberAccess => IsIndexedDefaultMemberAccess || IsNonIndexedDefaultMemberAccess;
7678
public bool IsProcedureCoercion { get; }
79+
public bool IsInnerRecursiveDefaultMemberAccess { get; }
7780
public int DefaultMemberRecursionDepth { get; }
7881

7982
public bool IsArrayAccess { get; }

0 commit comments

Comments
 (0)