Skip to content

Commit

Permalink
Do not Let coerce on Property Let regardless of type
Browse files Browse the repository at this point in the history
  • Loading branch information
MDoerner committed Sep 14, 2019
1 parent 0a3d83d commit f02dd6a
Show file tree
Hide file tree
Showing 3 changed files with 95 additions and 2 deletions.
Expand Up @@ -63,7 +63,8 @@ private static IBoundExpression Resolve(IBoundExpression wrappedExpression, Pars
|| !wrappedDeclaration.IsObject
&& !(wrappedDeclaration.IsObjectArray
&& wrappedExpression is IndexExpression indexExpression
&& indexExpression.IsArrayAccess))
&& indexExpression.IsArrayAccess)
|| wrappedDeclaration.DeclarationType == DeclarationType.PropertyLet)
{
return wrappedExpression;
}
Expand Down
50 changes: 50 additions & 0 deletions RubberduckTests/Grammar/ResolverTests.cs
Expand Up @@ -4632,6 +4632,56 @@ End Sub
}
}

[Test]
[Category("Grammar")]
[Category("Resolver")]
[TestCase(" cls.Baz = fooBar", 5, 12)]
[TestCase(" Let cls.Baz = fooBar", 9, 16)]
//This prevents problems with some types in libraries like OLE_COLOR, which are not really classes.
public void LetCoercionOnPropertyLetNeverDoesAnything(string statement, int selectionStartColumn, int selectionEndColumn)
{
var class1Code = @"
Public Function Foo() As Long
Attribute Foo.VB_UserMemId = 0
End Function
";

var class2Code = @"
Public Property Let Baz(RHS As Class1)
End Property
Public Property Get Baz() As Class1
Attribute Baz.VB_UserMemId = 0
End Property
";

var moduleCode = $@"
Private Function Foo() As Variant
Dim cls As New Class2
Dim fooBar As New Class1
{statement}
End Function
";

var vbe = MockVbeBuilder.BuildFromModules(
("Class1", class1Code, ComponentType.ClassModule),
("Class2", class2Code, ComponentType.ClassModule),
("Module1", moduleCode, ComponentType.StandardModule));

var selection = new Selection(5, selectionStartColumn, 5, selectionEndColumn);

using (var state = Resolve(vbe.Object))
{
var module = state.DeclarationFinder.AllModules.First(qmn => qmn.ComponentName == "Module1");
var qualifiedSelection = new QualifiedSelection(module, selection);
var defaultMemberReferences = state.DeclarationFinder.IdentifierReferences(qualifiedSelection);
var failedLetCoercionReferences = state.DeclarationFinder.FailedLetCoercions(module);

Assert.IsFalse(defaultMemberReferences.Any());
Assert.IsFalse(failedLetCoercionReferences.Any());
}
}

[Test]
[Category("Grammar")]
[Category("Resolver")]
Expand Down
@@ -1,10 +1,10 @@
using System;
using System.Collections.Generic;
using System.Linq;
using System.Threading;
using NUnit.Framework;
using Rubberduck.Inspections.Concrete;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.VBEditor;
using Rubberduck.VBEditor.SafeComWrappers;
Expand Down Expand Up @@ -1378,6 +1378,48 @@ End Sub
Assert.AreEqual(expectedSelection, actualSelection);
}

[Test]
[Category("Grammar")]
[Category("Resolver")]
[TestCase(" cls.Baz = fooBar")]
[TestCase(" Let cls.Baz = fooBar")]
//This prevents problems with some types in libraries like OLE_COLOR, which are not really classes.
//See issue #4997 at https://github.com/rubberduck-vba/Rubberduck/issues/4997
public void PropertyLetOnLHS_NoResult(string statement)
{
var class1Code = @"
Public Function Foo() As Long
Attribute Foo.VB_UserMemId = 0
End Function
";

var class2Code = @"
Public Property Let Baz(RHS As Class1)
End Property
Public Property Get Baz() As Class1
Attribute Baz.VB_UserMemId = 0
End Property
";

var moduleCode = $@"
Private Function Foo() As Variant
Dim cls As New Class2
Dim fooBar As New Class1
{statement}
End Function
";

var vbe = MockVbeBuilder.BuildFromModules(
("Class1", class1Code, ComponentType.ClassModule),
("Class2", class2Code, ComponentType.ClassModule),
("Module1", moduleCode, ComponentType.StandardModule));

var inspectionResults = InspectionResults(vbe.Object);

Assert.IsFalse(inspectionResults.Any());
}

protected override IInspection InspectionUnderTest(RubberduckParserState state)
{
return new ObjectVariableNotSetInspection(state);
Expand Down

0 comments on commit f02dd6a

Please sign in to comment.