Skip to content

Commit 0fb6336

Browse files
authored
Merge pull request #4627 from retailcoder/redim
Disable MissingAttributeInspection + edge-case fix for ObjectVariableNotSet
2 parents 0e28e45 + 68e6b6b commit 0fb6336

File tree

8 files changed

+984
-580
lines changed

8 files changed

+984
-580
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8,10 +8,10 @@
88
using Rubberduck.Parsing.Grammar;
99
using Rubberduck.Parsing.Inspections;
1010
using Rubberduck.Parsing.Inspections.Abstract;
11-
using Rubberduck.Resources.Inspections;
1211
using Rubberduck.Parsing.Symbols;
1312
using Rubberduck.Parsing.VBA;
1413
using Rubberduck.Parsing.VBA.Parsing;
14+
using Rubberduck.Resources.Inspections;
1515

1616
namespace Rubberduck.Inspections.Concrete
1717
{
@@ -33,7 +33,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3333
return Listener.Contexts.Select(context =>
3434
{
3535
var name = string.Format(InspectionResults.MissingAttributeInspection, context.MemberName.MemberName,
36-
((VBAParser.AnnotationContext) context.Context).annotationName().GetText());
36+
((VBAParser.AnnotationContext)context.Context).annotationName().GetText());
3737
return new QualifiedContextInspectionResult(this, name, context);
3838
});
3939
}

Rubberduck.Core/Properties/Settings.Designer.cs

Lines changed: 288 additions & 310 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Core/Properties/Settings.settings

Lines changed: 240 additions & 259 deletions
Large diffs are not rendered by default.

Rubberduck.Core/Rubberduck.Core.csproj

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -110,6 +110,13 @@
110110
<DependentUpon>%(Filename).cs</DependentUpon>
111111
</EmbeddedResource>
112112
</ItemGroup>
113+
<ItemGroup>
114+
<Compile Update="Properties\Settings.Designer.cs">
115+
<DesignTime>True</DesignTime>
116+
<AutoGen>True</AutoGen>
117+
<DependentUpon>Settings.settings</DependentUpon>
118+
</Compile>
119+
</ItemGroup>
113120
<!-- END WINDOWS FORMS WORKAROUND SECTION -->
114121

115122
</Project>

Rubberduck.Core/app.config

Lines changed: 402 additions & 0 deletions
Large diffs are not rendered by default.

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 18 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -349,13 +349,24 @@ private static string CorrectlyFormatedDescription(string literalDescription)
349349
/// </summary>
350350
public bool IsEnumeratorMember => _attributes.Any(a => a.Name.EndsWith("VB_UserMemId") && a.Values.Contains("-4"));
351351

352-
public virtual bool IsObject =>
353-
AsTypeName == Tokens.Object || (
354-
AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.ClassModule) ??
355-
!AsTypeIsBaseType
356-
&& !IsArray
357-
&& !DeclarationType.HasFlag(DeclarationType.UserDefinedType)
358-
&& !DeclarationType.HasFlag(DeclarationType.Enumeration));
352+
public virtual bool IsObject
353+
{
354+
get
355+
{
356+
if (AsTypeName == Tokens.Object ||
357+
(AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.ClassModule) ?? false))
358+
{
359+
return true;
360+
}
361+
362+
var isIntrinsic = AsTypeIsBaseType
363+
|| IsArray
364+
|| (AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.UserDefinedType) ?? false)
365+
|| (AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.Enumeration) ?? false);
366+
367+
return !isIntrinsic;
368+
}
369+
}
359370

360371
public void AddReference(
361372
QualifiedModuleName module,

Rubberduck.Parsing/Symbols/PropertyDeclaration.cs

Lines changed: 14 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -44,8 +44,20 @@ protected PropertyDeclaration(
4444
attributes)
4545
{ }
4646

47-
public override bool IsObject =>
48-
base.IsObject || (Parameters.OrderBy(p => p.Selection).LastOrDefault()?.IsObject ?? false);
47+
public override bool IsObject
48+
{
49+
get
50+
{
51+
if (base.IsObject)
52+
{
53+
return true;
54+
}
55+
56+
return (DeclarationType == DeclarationType.PropertyLet ||
57+
DeclarationType == DeclarationType.PropertySet) &&
58+
(Parameters.OrderBy(p => p.Selection).LastOrDefault()?.IsObject ?? false);
59+
}
60+
}
4961

5062
/// <inheritdoc/>
5163
protected abstract override bool Implements(IInterfaceExposable member);

RubberduckTests/Inspections/ObjectVariableNotSetInspectionTests.cs

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,19 @@ namespace RubberduckTests.Inspections
1111
[TestFixture]
1212
public class ObjectVariableNotSetInspectionTests
1313
{
14+
[Test]
15+
[Category("Inspections")]
16+
public void ObjectVariableNotSet_NotResultForNonObjectPropertyGetWithObjectArgument()
17+
{
18+
var expectedResultCount = 0;
19+
var input = @"
20+
Public Property Get Foo(ByVal bar As Object) As Boolean
21+
Foo = True
22+
End Property
23+
";
24+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectedResultCount);
25+
}
26+
1427
[Test]
1528
[Category("Inspections")]
1629
public void ObjectVariableNotSet_AlsoAssignedToNothing_ReturnsNoResult()

0 commit comments

Comments
 (0)