Skip to content

Commit f02dd6a

Browse files
committed
Do not Let coerce on Property Let regardless of type
1 parent 0a3d83d commit f02dd6a

File tree

3 files changed

+95
-2
lines changed

3 files changed

+95
-2
lines changed

Rubberduck.Parsing/Binding/Bindings/LetCoercionDefaultBinding.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -63,7 +63,8 @@ private static IBoundExpression Resolve(IBoundExpression wrappedExpression, Pars
6363
|| !wrappedDeclaration.IsObject
6464
&& !(wrappedDeclaration.IsObjectArray
6565
&& wrappedExpression is IndexExpression indexExpression
66-
&& indexExpression.IsArrayAccess))
66+
&& indexExpression.IsArrayAccess)
67+
|| wrappedDeclaration.DeclarationType == DeclarationType.PropertyLet)
6768
{
6869
return wrappedExpression;
6970
}

RubberduckTests/Grammar/ResolverTests.cs

Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4632,6 +4632,56 @@ End Sub
46324632
}
46334633
}
46344634

4635+
[Test]
4636+
[Category("Grammar")]
4637+
[Category("Resolver")]
4638+
[TestCase(" cls.Baz = fooBar", 5, 12)]
4639+
[TestCase(" Let cls.Baz = fooBar", 9, 16)]
4640+
//This prevents problems with some types in libraries like OLE_COLOR, which are not really classes.
4641+
public void LetCoercionOnPropertyLetNeverDoesAnything(string statement, int selectionStartColumn, int selectionEndColumn)
4642+
{
4643+
var class1Code = @"
4644+
Public Function Foo() As Long
4645+
Attribute Foo.VB_UserMemId = 0
4646+
End Function
4647+
";
4648+
4649+
var class2Code = @"
4650+
Public Property Let Baz(RHS As Class1)
4651+
End Property
4652+
4653+
Public Property Get Baz() As Class1
4654+
Attribute Baz.VB_UserMemId = 0
4655+
End Property
4656+
";
4657+
4658+
var moduleCode = $@"
4659+
Private Function Foo() As Variant
4660+
Dim cls As New Class2
4661+
Dim fooBar As New Class1
4662+
{statement}
4663+
End Function
4664+
";
4665+
4666+
var vbe = MockVbeBuilder.BuildFromModules(
4667+
("Class1", class1Code, ComponentType.ClassModule),
4668+
("Class2", class2Code, ComponentType.ClassModule),
4669+
("Module1", moduleCode, ComponentType.StandardModule));
4670+
4671+
var selection = new Selection(5, selectionStartColumn, 5, selectionEndColumn);
4672+
4673+
using (var state = Resolve(vbe.Object))
4674+
{
4675+
var module = state.DeclarationFinder.AllModules.First(qmn => qmn.ComponentName == "Module1");
4676+
var qualifiedSelection = new QualifiedSelection(module, selection);
4677+
var defaultMemberReferences = state.DeclarationFinder.IdentifierReferences(qualifiedSelection);
4678+
var failedLetCoercionReferences = state.DeclarationFinder.FailedLetCoercions(module);
4679+
4680+
Assert.IsFalse(defaultMemberReferences.Any());
4681+
Assert.IsFalse(failedLetCoercionReferences.Any());
4682+
}
4683+
}
4684+
46354685
[Test]
46364686
[Category("Grammar")]
46374687
[Category("Resolver")]

RubberduckTests/Inspections/ObjectVariableNotSetInspectionTests.cs

Lines changed: 43 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,10 @@
11
using System;
2-
using System.Collections.Generic;
32
using System.Linq;
43
using System.Threading;
54
using NUnit.Framework;
65
using Rubberduck.Inspections.Concrete;
76
using Rubberduck.Parsing.Inspections.Abstract;
7+
using Rubberduck.Parsing.Symbols;
88
using Rubberduck.Parsing.VBA;
99
using Rubberduck.VBEditor;
1010
using Rubberduck.VBEditor.SafeComWrappers;
@@ -1378,6 +1378,48 @@ End Sub
13781378
Assert.AreEqual(expectedSelection, actualSelection);
13791379
}
13801380

1381+
[Test]
1382+
[Category("Grammar")]
1383+
[Category("Resolver")]
1384+
[TestCase(" cls.Baz = fooBar")]
1385+
[TestCase(" Let cls.Baz = fooBar")]
1386+
//This prevents problems with some types in libraries like OLE_COLOR, which are not really classes.
1387+
//See issue #4997 at https://github.com/rubberduck-vba/Rubberduck/issues/4997
1388+
public void PropertyLetOnLHS_NoResult(string statement)
1389+
{
1390+
var class1Code = @"
1391+
Public Function Foo() As Long
1392+
Attribute Foo.VB_UserMemId = 0
1393+
End Function
1394+
";
1395+
1396+
var class2Code = @"
1397+
Public Property Let Baz(RHS As Class1)
1398+
End Property
1399+
1400+
Public Property Get Baz() As Class1
1401+
Attribute Baz.VB_UserMemId = 0
1402+
End Property
1403+
";
1404+
1405+
var moduleCode = $@"
1406+
Private Function Foo() As Variant
1407+
Dim cls As New Class2
1408+
Dim fooBar As New Class1
1409+
{statement}
1410+
End Function
1411+
";
1412+
1413+
var vbe = MockVbeBuilder.BuildFromModules(
1414+
("Class1", class1Code, ComponentType.ClassModule),
1415+
("Class2", class2Code, ComponentType.ClassModule),
1416+
("Module1", moduleCode, ComponentType.StandardModule));
1417+
1418+
var inspectionResults = InspectionResults(vbe.Object);
1419+
1420+
Assert.IsFalse(inspectionResults.Any());
1421+
}
1422+
13811423
protected override IInspection InspectionUnderTest(RubberduckParserState state)
13821424
{
13831425
return new ObjectVariableNotSetInspection(state);

0 commit comments

Comments
 (0)