Skip to content

Commit

Permalink
Merge pull request #5151 from BZngr/4969_ModuleRenames
Browse files Browse the repository at this point in the history
Rename conflict detection respects Project scope
  • Loading branch information
bclothier committed Sep 18, 2019
2 parents f5e88d1 + f39f248 commit 629deec
Show file tree
Hide file tree
Showing 2 changed files with 66 additions and 5 deletions.
Expand Up @@ -1302,7 +1302,8 @@ public IEnumerable<Declaration> FindNewDeclarationNameConflicts(string newName,
return Enumerable.Empty<Declaration>();
}

var identifierMatches = MatchName(newName).ToList();
var identifierMatches = MatchName(newName).Where(match => match.ProjectId == renameTarget.ProjectId);

if (!identifierMatches.Any())
{
return Enumerable.Empty<Declaration>();
Expand All @@ -1327,7 +1328,7 @@ public IEnumerable<Declaration> FindNewDeclarationNameConflicts(string newName,
|| idm.DeclarationType.HasFlag(DeclarationType.Variable)
&& idm.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Module)
&& renameTarget.References.Any(renameTargetRef => renameTargetRef.QualifiedModuleName == idm.ParentDeclaration.QualifiedModuleName))
.ToList();
.ToList();

if (referenceConflicts.Any())
{
Expand All @@ -1342,7 +1343,8 @@ public IEnumerable<Declaration> FindNewDeclarationNameConflicts(string newName,
renameTargetModule,
renameTarget.ParentDeclaration,
idm)
&& IsConflictingMember(renameTarget, renameTargetModule, idm));
&& IsConflictingMember(renameTarget, renameTargetModule, idm))
.ToList();

return declarationConflicts;
}
Expand Down
63 changes: 61 additions & 2 deletions RubberduckTests/Symbols/DeclarationFinderTests.cs
Expand Up @@ -12,6 +12,7 @@
using Rubberduck.Common;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using System;

namespace RubberduckTests.Symbols
{
Expand Down Expand Up @@ -445,6 +446,45 @@ End Sub
Assert.AreEqual(isConflict, conflicts.Where(cf => cf.IdentifierName.Equals(nameToCheck)).Any(), ConflictMessage(isConflict, nameToCheck, conflicts));
}


//https://github.com/rubberduck-vba/Rubberduck/issues/4969
private const string projectOneModuleName = "projectOneModule";
private const string projectTwoModuleName = "projectTwoModule";
[TestCase(projectOneModuleName, 0)] //Duplicate module name found in a separate project
[TestCase(projectTwoModuleName, 1)] //Duplicate module name found in the same project
[Category("Resolver")]
public void DeclarationFinder_NameConflictDetectionRespectsProjectScope(string proposedTestModuleName, int expectedCount)
{

string renameTargetModuleName = "TargetModule";

string moduleContent = $"Private Sub Foo(){Environment.NewLine}End Sub";

var projectOneContent = new TestComponentSpecification[]
{
new TestComponentSpecification(projectOneModuleName, moduleContent, ComponentType.StandardModule)
};

var projectTwoContent = new TestComponentSpecification[]
{
new TestComponentSpecification(renameTargetModuleName, moduleContent, ComponentType.StandardModule),
new TestComponentSpecification(projectTwoModuleName, moduleContent, ComponentType.StandardModule)
};

var vbe = BuildProjects(new (string, IEnumerable<TestComponentSpecification>)[]
{("ProjectOne", projectOneContent),("ProjectTwo", projectTwoContent)});

using(var parser = MockParser.CreateAndParse(vbe))
{
var target = parser.DeclarationFinder.UserDeclarations(DeclarationType.ProceduralModule)
.FirstOrDefault(item => item.IdentifierName.Equals(renameTargetModuleName));

var results = parser.DeclarationFinder.FindNewDeclarationNameConflicts(proposedTestModuleName, target);

Assert.AreEqual(expectedCount, results.Count());
}
}

private static string ConflictMessage(bool isConflict, string name, IEnumerable<Declaration> conflicts)
{
return isConflict ? $"Identifier '{name}' is a conflict but was not identified" : $"Identifier '{name}' was incorrectly found as a conflict";
Expand Down Expand Up @@ -498,14 +538,33 @@ private void AddTestComponent(AccessibilityTestsDataObject tdo, string moduleIde
}

private IVBE BuildProject(string projectName, List<TestComponentSpecification> testComponents)
{
var projectDefs = new (string, IEnumerable<TestComponentSpecification>)[] { (projectName, testComponents) };
return BuildProjects(projectDefs);
}

private IVBE BuildProjects(IEnumerable<(string ProjectName, IEnumerable<TestComponentSpecification> TestComponents)> projectDefinitions)
{
var builder = new MockVbeBuilder();
foreach (var projectDef in projectDefinitions)
{
builder = AddProject(builder, projectDef.ProjectName, projectDef.TestComponents);
}
return builder.Build().Object;
}

private MockVbeBuilder AddProject(MockVbeBuilder builder, string projectName, IEnumerable<TestComponentSpecification> testComponents)
{
var enclosingProjectBuilder = builder.ProjectBuilder(projectName, ProjectProtection.Unprotected);

testComponents.ForEach(c => enclosingProjectBuilder.AddComponent(c.Name, c.ModuleType, c.Content));
foreach (var testComponent in testComponents)
{
enclosingProjectBuilder.AddComponent(testComponent.Name, testComponent.ModuleType, testComponent.Content);
}

var enclosingProject = enclosingProjectBuilder.Build();
builder.AddProject(enclosingProject);
return builder.Build().Object;
return builder;
}

private IVBComponent RetrieveComponent(AccessibilityTestsDataObject tdo, string componentName)
Expand Down

0 comments on commit 629deec

Please sign in to comment.