Skip to content

Commit bc12cf4

Browse files
authored
Merge pull request #3566 from Vogel612/bughunting
Hunting longstanding "simple" bugs
2 parents f398240 + ef11a05 commit bc12cf4

File tree

5 files changed

+111
-6
lines changed

5 files changed

+111
-6
lines changed

RetailCoder.VBE/Refactorings/Rename/RenameRefactoring.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -476,7 +476,9 @@ private void RenameStandardElements(Declaration target, string newName)
476476

477477
private void RenameReferences(Declaration target, string newName)
478478
{
479-
var modules = target.References.GroupBy(r => r.QualifiedModuleName);
479+
var modules = target.References
480+
.Where(reference => reference.Context.GetText() != "Me")
481+
.GroupBy(r => r.QualifiedModuleName);
480482
foreach (var grouping in modules)
481483
{
482484
_modulesToRewrite.Add(grouping.Key);

Rubberduck.Inspections/Concrete/MemberNotOnInterfaceInspection.cs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -23,16 +23,15 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2323

2424
var targets = Declarations.Where(decl => decl.AsTypeDeclaration != null &&
2525
!decl.AsTypeDeclaration.IsUserDefined &&
26-
decl.AsTypeDeclaration.DeclarationType == DeclarationType.ClassModule &&
26+
decl.AsTypeDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule) &&
2727
((ClassModuleDeclaration)decl.AsTypeDeclaration).IsExtensible)
2828
.SelectMany(decl => decl.References).ToList();
29-
3029
return from access in unresolved
3130
let callingContext = targets.FirstOrDefault(usage => usage.Context.Equals(access.CallingContext))
3231
where callingContext != null
3332
select new DeclarationInspectionResult(this,
34-
string.Format(InspectionsUI.MemberNotOnInterfaceInspectionResultFormat, access.IdentifierName, callingContext.Declaration.AsTypeDeclaration.IdentifierName),
35-
access);
33+
string.Format(InspectionsUI.MemberNotOnInterfaceInspectionResultFormat, access.IdentifierName, callingContext.Declaration.AsTypeDeclaration.IdentifierName),
34+
access);
3635
}
3736
}
3837
}

Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -174,7 +174,7 @@ private void ResolveDefault(
174174
{
175175
var lexpression = expression as VBAParser.LExpressionContext
176176
?? expression.GetChild<VBAParser.LExpressionContext>(0)
177-
?? (expression as VBAParser.LExprContext
177+
?? (expression as VBAParser.LExprContext
178178
?? expression.GetChild<VBAParser.LExprContext>(0))?.lExpression();
179179

180180
if (lexpression != null)

RubberduckTests/Inspections/MemberNotOnInterfaceInspectionTests.cs

Lines changed: 62 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -265,5 +265,67 @@ Dim dict As Dictionary
265265
Assert.IsFalse(inspectionResults.Any());
266266
}
267267
}
268+
269+
[TestMethod]
270+
[DeploymentItem(@"Testfiles\")]
271+
[TestCategory("Inspections")]
272+
public void MemberNotOnInterface_CatchesInvalidUseOfMember()
273+
{
274+
const string userForm1Code = @"
275+
Private _fooBar As String
276+
277+
Public Property Let FooBar(value As String)
278+
_fooBar = value
279+
End Property
280+
281+
Public Property Get FooBar() As String
282+
FooBar = _fooBar
283+
End Property
284+
";
285+
286+
const string analyzedCode = @"Option Explicit
287+
288+
Sub FizzBuzz()
289+
290+
Dim bar As UserForm1
291+
Set bar = New UserForm1
292+
bar.FooBar = ""FooBar""
293+
294+
Dim foo As UserForm
295+
Set foo = New UserForm1
296+
foo.FooBar = ""BarFoo""
297+
298+
End Sub
299+
";
300+
var mockVbe = new MockVbeBuilder();
301+
var projectBuilder = mockVbe.ProjectBuilder("testproject", ProjectProtection.Unprotected);
302+
projectBuilder.MockUserFormBuilder("UserForm1", userForm1Code).MockProjectBuilder()
303+
.AddComponent("ReferencingModule", ComponentType.StandardModule, analyzedCode)
304+
//.AddReference("Excel", MockVbeBuilder.LibraryPathMsExcel)
305+
.AddReference("MSForms", MockVbeBuilder.LibraryPathMsForms);
306+
307+
mockVbe.AddProject(projectBuilder.Build());
308+
309+
310+
var parser = MockParser.Create(mockVbe.Build().Object);
311+
312+
//parser.State.AddTestLibrary("Excel.1.8.xml");
313+
parser.State.AddTestLibrary("MSForms.2.0.xml");
314+
315+
parser.Parse(new CancellationTokenSource());
316+
if (parser.State.Status >= ParserState.Error)
317+
{
318+
Assert.Inconclusive("Parser Error");
319+
}
320+
321+
using (var state = parser.State)
322+
{
323+
var inspection = new MemberNotOnInterfaceInspection(state);
324+
var inspectionResults = inspection.GetInspectionResults();
325+
326+
Assert.IsTrue(inspectionResults.Any());
327+
}
328+
329+
}
268330
}
269331
}

RubberduckTests/Refactoring/RenameTests.cs

Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1962,6 +1962,48 @@ Dim va|l1 As Integer
19621962
Assert.IsFalse(renameViewModel.IsValidName);
19631963
}
19641964

1965+
1966+
[TestMethod]
1967+
[TestCategory("Refactorings")]
1968+
[TestCategory("Rename")]
1969+
public void RenameRefactoring_RenameClassModule_DoesNotChangeMeReferences()
1970+
{
1971+
const string newName = "RenamedClassModule";
1972+
1973+
//Input
1974+
const string inputCode =
1975+
@"Property Get Self() As IClassModule
1976+
Set Self = Me
1977+
End Property";
1978+
1979+
var selection = new Selection(3, 27, 3, 27);
1980+
1981+
IVBComponent component;
1982+
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, "ClassModule1", ComponentType.ClassModule, out component, selection);
1983+
using (var state = MockParser.CreateAndParse(vbe.Object))
1984+
{
1985+
1986+
var qualifiedSelection = new QualifiedSelection(new QualifiedModuleName(component), selection);
1987+
1988+
var msgbox = new Mock<IMessageBox>();
1989+
msgbox.Setup(m => m.Show(It.IsAny<string>(), It.IsAny<string>(), MessageBoxButtons.YesNo, It.IsAny<MessageBoxIcon>()))
1990+
.Returns(DialogResult.Yes);
1991+
1992+
var vbeWrapper = vbe.Object;
1993+
var model = new RenameModel(vbeWrapper, state, qualifiedSelection) { NewName = newName };
1994+
model.Target = model.Declarations.FirstOrDefault(i => i.DeclarationType == DeclarationType.ClassModule && i.IdentifierName == "ClassModule1");
1995+
1996+
//SetupFactory
1997+
var factory = SetupFactory(model);
1998+
1999+
var refactoring = new RenameRefactoring(vbeWrapper, factory.Object, msgbox.Object, state);
2000+
refactoring.Refactor(model.Target);
2001+
2002+
Assert.AreSame(newName, component.CodeModule.Name);
2003+
Assert.AreEqual(inputCode, component.CodeModule.GetLines(0, component.CodeModule.CountOfLines));
2004+
}
2005+
2006+
}
19652007
#endregion
19662008

19672009
#region Test Execution

0 commit comments

Comments
 (0)