Skip to content

Commit 811c901

Browse files
authored
Merge branch 'next' into next
2 parents 5ab7103 + 402674d commit 811c901

File tree

4 files changed

+172
-65
lines changed

4 files changed

+172
-65
lines changed

RetailCoder.VBE/Properties/AssemblyInfo.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,5 +31,5 @@
3131
// You can specify all the values or you can default the Build and Revision Numbers
3232
// by using the '*' as shown below:
3333
// [assembly: AssemblyVersion("1.0.*")]
34-
[assembly: AssemblyVersion("2.0.12.*")]
35-
[assembly: AssemblyFileVersion("2.0.12.0")]
34+
[assembly: AssemblyVersion("2.0.13.*")]
35+
[assembly: AssemblyFileVersion("2.0.13.0")]

RetailCoder.VBE/Refactorings/Rename/RenameRefactoring.cs

Lines changed: 3 additions & 63 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@
1414
using Rubberduck.VBEditor;
1515
using Rubberduck.VBEditor.SafeComWrappers;
1616
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
17+
using System;
1718

1819
namespace Rubberduck.Refactorings.Rename
1920
{
@@ -92,68 +93,6 @@ public void Refactor(Declaration target)
9293
pane.Selection = oldSelection;
9394
}
9495
}
95-
96-
private Declaration FindDeclarationForIdentifier()
97-
{
98-
var values = _model.Declarations.Where(item =>
99-
_model.NewName == item.IdentifierName
100-
&& ((item.Scope.Contains(_model.Target.Scope)
101-
|| (item.ParentScope == null && string.IsNullOrEmpty(_model.Target.ParentScope))
102-
|| (item.ParentScope != null && _model.Target.ParentScope.Contains(item.ParentScope))))
103-
).ToList();
104-
105-
if (values.Any())
106-
{
107-
return values.FirstOrDefault();
108-
}
109-
110-
foreach (var reference in _model.Target.References)
111-
{
112-
var targetReference = reference;
113-
var potentialDeclarations = _model.Declarations.Where(item => !item.IsBuiltIn
114-
&& item.ProjectId == targetReference.Declaration.ProjectId
115-
&& ((item.Context != null
116-
&& item.Context.Start.Line <= targetReference.Selection.StartLine
117-
&& item.Context.Stop.Line >= targetReference.Selection.EndLine)
118-
|| (item.Selection.StartLine <= targetReference.Selection.StartLine
119-
&& item.Selection.EndLine >= targetReference.Selection.EndLine))
120-
&& item.QualifiedName.QualifiedModuleName.ComponentName == targetReference.QualifiedModuleName.ComponentName);
121-
122-
var currentSelection = new Selection(0, 0, int.MaxValue, int.MaxValue);
123-
124-
Declaration target = null;
125-
foreach (var item in potentialDeclarations)
126-
{
127-
var startLine = item.Context == null ? item.Selection.StartLine : item.Context.Start.Line;
128-
var endLine = item.Context == null ? item.Selection.EndLine : item.Context.Stop.Column;
129-
var startColumn = item.Context == null ? item.Selection.StartColumn : item.Context.Start.Column;
130-
var endColumn = item.Context == null ? item.Selection.EndColumn : item.Context.Stop.Column;
131-
132-
var selection = new Selection(startLine, startColumn, endLine, endColumn);
133-
134-
if (currentSelection.Contains(selection))
135-
{
136-
currentSelection = selection;
137-
target = item;
138-
}
139-
}
140-
141-
if (target == null) { continue; }
142-
143-
values = _model.Declarations.Where(item => (item.Scope.Contains(target.Scope)
144-
|| (item.ParentScope == null && string.IsNullOrEmpty(target.ParentScope))
145-
|| (item.ParentScope != null && target.ParentScope.Contains(item.ParentScope)))
146-
&& _model.NewName == item.IdentifierName).ToList();
147-
148-
if (values.Any())
149-
{
150-
return values.FirstOrDefault();
151-
}
152-
}
153-
154-
return null;
155-
}
156-
15796
private static readonly DeclarationType[] ModuleDeclarationTypes =
15897
{
15998
DeclarationType.ClassModule,
@@ -162,7 +101,8 @@ private Declaration FindDeclarationForIdentifier()
162101

163102
private void Rename()
164103
{
165-
var declaration = FindDeclarationForIdentifier();
104+
var declaration = _state.DeclarationFinder.GetDeclarationsAccessibleToScope(_model.Target, _model.Declarations)
105+
.Where(d => d.IdentifierName.Equals(_model.NewName, StringComparison.InvariantCultureIgnoreCase)).FirstOrDefault();
166106
if (declaration != null)
167107
{
168108
var message = string.Format(RubberduckUI.RenameDialog_ConflictingNames, _model.NewName,

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 54 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -747,5 +747,59 @@ private ConcurrentBag<Declaration> FindEventHandlers(IEnumerable<Declaration> de
747747

748748
return new ConcurrentBag<Declaration>(handlers);
749749
}
750+
751+
public IEnumerable<Declaration> GetDeclarationsAccessibleToScope(Declaration target, IEnumerable<Declaration> declarations)
752+
{
753+
if (target == null) { return Enumerable.Empty<Declaration>(); }
754+
755+
return declarations
756+
.Where(candidateDeclaration =>
757+
(
758+
IsDeclarationInTheSameProcedure(candidateDeclaration, target)
759+
|| IsDeclarationChildOfTheScope(candidateDeclaration, target)
760+
|| IsModuleLevelDeclarationOfTheScope(candidateDeclaration, target)
761+
|| IsProjectGlobalDeclaration(candidateDeclaration, target)
762+
)).Distinct();
763+
}
764+
765+
private bool IsDeclarationInTheSameProcedure(Declaration candidateDeclaration, Declaration scopingDeclaration)
766+
{
767+
return candidateDeclaration.ParentScope == scopingDeclaration.ParentScope;
768+
}
769+
770+
private bool IsDeclarationChildOfTheScope(Declaration candidateDeclaration, Declaration scopingDeclaration)
771+
{
772+
return scopingDeclaration == candidateDeclaration.ParentDeclaration;
773+
}
774+
775+
private bool IsModuleLevelDeclarationOfTheScope(Declaration candidateDeclaration, Declaration scopingDeclaration)
776+
{
777+
if (candidateDeclaration.ParentDeclaration == null)
778+
{
779+
return false;
780+
}
781+
return candidateDeclaration.ComponentName == scopingDeclaration.ComponentName
782+
&& !IsDeclaredWithinMethodOrProperty(candidateDeclaration.ParentDeclaration.Context);
783+
}
784+
785+
private bool IsProjectGlobalDeclaration(Declaration candidateDeclaration, Declaration scopingDeclaration)
786+
{
787+
return candidateDeclaration.ProjectName == scopingDeclaration.ProjectName
788+
&& !(candidateDeclaration.ParentScopeDeclaration is ClassModuleDeclaration)
789+
&& (candidateDeclaration.Accessibility == Accessibility.Public
790+
|| ((candidateDeclaration.Accessibility == Accessibility.Implicit)
791+
&& (candidateDeclaration.ParentScopeDeclaration is ProceduralModuleDeclaration)));
792+
}
793+
794+
private bool IsDeclaredWithinMethodOrProperty(RuleContext procedureContextCandidate)
795+
{
796+
if (procedureContextCandidate == null) { return false; }
797+
798+
return (procedureContextCandidate is VBAParser.SubStmtContext)
799+
|| (procedureContextCandidate is VBAParser.FunctionStmtContext)
800+
|| (procedureContextCandidate is VBAParser.PropertyLetStmtContext)
801+
|| (procedureContextCandidate is VBAParser.PropertyGetStmtContext)
802+
|| (procedureContextCandidate is VBAParser.PropertySetStmtContext);
803+
}
750804
}
751805
}

RubberduckTests/Refactoring/RenameTests.cs

Lines changed: 113 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,60 @@ namespace RubberduckTests.Refactoring
2020
[TestClass]
2121
public class RenameTests : VbeTestBase
2222
{
23+
[TestMethod]
24+
public void RenameRefactoring_RenameSub_Issue2727()
25+
{
26+
//Input
27+
string inputCode = GetIssue2727ExampleCode();
28+
29+
Selection selection = Select2727Variable();
30+
31+
//New name provided by the user - no conflicts
32+
var userEnteredName = "Value";
33+
34+
//Expectation
35+
//Expecation is that the messageBox.Show() is not invoked
36+
37+
//Arrange
38+
var builder = new MockVbeBuilder();
39+
IVBComponent component;
40+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component, selection);
41+
var project = vbe.Object.VBProjects[0];
42+
var module = project.VBComponents[0].CodeModule;
43+
var mockHost = new Mock<IHostApplication>();
44+
mockHost.SetupAllProperties();
45+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
46+
47+
parser.Parse(new CancellationTokenSource());
48+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
49+
50+
var qualifiedSelection = new QualifiedSelection(new QualifiedModuleName(component), selection);
51+
52+
var msgbox = new Mock<IMessageBox>();
53+
msgbox.Setup(m => m.Show(It.IsAny<string>(), It.IsAny<string>(), MessageBoxButtons.YesNo, It.IsAny<MessageBoxIcon>()))
54+
.Returns(DialogResult.Yes);
55+
56+
var vbeWrapper = vbe.Object;
57+
var model = new RenameModel(vbeWrapper, parser.State, qualifiedSelection, msgbox.Object) { NewName = userEnteredName };
58+
59+
//SetupFactory
60+
var factory = SetupFactory(model);
61+
62+
//Act
63+
var refactoring = new RenameRefactoring(vbeWrapper, factory.Object, msgbox.Object, parser.State);
64+
refactoring.Refactor(qualifiedSelection);
65+
66+
//Assert
67+
//#2727 bug describes a scenario where a declaration collision is detected where none exists.
68+
//The result of detecting one or more collisions is that the messagebox is presented to the user
69+
//To see if he wants to continue with the Renaming process.
70+
//To pass this test, FindDeclarationForIdentifier() should find zero collisions and therefore
71+
//skips the logic that presents the message box to the user.
72+
string failMsg = "RenameRefactoring found a conflicting declaration where none exists.";
73+
msgbox.Verify(m => m.Show(It.IsAny<string>(), It.IsAny<string>(), MessageBoxButtons.YesNo, It.IsAny<MessageBoxIcon>()), Times.Never, failMsg);
74+
}
75+
76+
2377
[TestMethod]
2478
public void RenameRefactoring_RenameSub()
2579
{
@@ -1421,5 +1475,64 @@ private static Mock<IRefactoringPresenterFactory<IRenamePresenter>> SetupFactory
14211475
}
14221476

14231477
#endregion
1478+
1479+
//Module code taken directly from Issue #2727 - choosing to rename "ic" in 'Let Industry'
1480+
//resulted in a false-positive name collision with parameter 'Value' in 'Let IndustryCode'.
1481+
private string GetIssue2727ExampleCode()
1482+
{
1483+
return
1484+
@"
1485+
Option Explicit
1486+
'@folder ""Data Objects""
1487+
1488+
Private pName As String
1489+
Private pIndustryCode As Long
1490+
Private pIndustry As String
1491+
Private pLastYearAppts As Long
1492+
Private pLastYearEmail As Long
1493+
1494+
Public Property Get IndustryCode() As String
1495+
IndustryCode = pIndustryCode
1496+
End Property
1497+
Public Property Let IndustryCode(ByVal Value As String)
1498+
pIndustryCode = Value
1499+
End Property
1500+
1501+
Public Property Get Industry() As String
1502+
Industry = pIndustry
1503+
End Property
1504+
Public Property Let Industry(ByVal ic As String)
1505+
pIndustry = ic
1506+
End Property
1507+
1508+
Public Property Get LastYearAppts() As Long
1509+
LastYearAppts = pLastYearAppts
1510+
End Property
1511+
Public Property Let LastYearAppts(ByVal Value As Long)
1512+
pLastYearAppts = Value
1513+
End Property
1514+
";
1515+
}
1516+
private Selection Select2727Variable()
1517+
{
1518+
var inputCode = GetIssue2727ExampleCode();
1519+
//Create the selection
1520+
var splitToken = new string[] { "\r\n" };
1521+
const string renameTarget = " ic ";
1522+
1523+
var lines = inputCode.Split(splitToken, System.StringSplitOptions.None);
1524+
int lineNumber = 0;
1525+
for (int idx = 0; idx < lines.Count() & lineNumber < 1; idx++)
1526+
{
1527+
if (lines[idx].Contains(renameTarget))
1528+
{
1529+
lineNumber = idx + 1;
1530+
}
1531+
}
1532+
var column = lines[lineNumber - 1].IndexOf(renameTarget) + 3; /*places cursor between the 'i' and 'c'*/
1533+
var selection = new Selection(lineNumber, column, lineNumber, column);
1534+
return selection;
1535+
}
1536+
14241537
}
14251538
}

0 commit comments

Comments
 (0)