Skip to content

Commit b7be5f4

Browse files
committed
fixes #2727
1 parent a6d26ef commit b7be5f4

File tree

4 files changed

+197
-63
lines changed

4 files changed

+197
-63
lines changed
Lines changed: 65 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,65 @@
1+
using Antlr4.Runtime;
2+
using Rubberduck.Parsing.Grammar;
3+
using Rubberduck.Parsing.Symbols;
4+
using System.Collections.Generic;
5+
using System.Linq;
6+
7+
namespace Rubberduck.Inspections
8+
{
9+
public static class AccessibilityEvaluator
10+
{
11+
public static IEnumerable<Declaration> GetDeclarationsAccessibleToScope(Declaration target, IEnumerable<Declaration> declarations)
12+
{
13+
if (target == null) { return Enumerable.Empty<Declaration>(); }
14+
15+
return declarations
16+
.Where(candidateDeclaration =>
17+
(
18+
IsDeclarationInTheSameProcedure(candidateDeclaration, target)
19+
|| IsDeclarationChildOfTheScope(candidateDeclaration, target)
20+
|| IsModuleLevelDeclarationOfTheScope(candidateDeclaration, target)
21+
|| IsProjectGlobalDeclaration(candidateDeclaration, target)
22+
)).Distinct();
23+
}
24+
25+
private static bool IsDeclarationInTheSameProcedure(Declaration candidateDeclaration, Declaration scopingDeclaration)
26+
{
27+
return candidateDeclaration.ParentScope == scopingDeclaration.ParentScope;
28+
}
29+
30+
private static bool IsDeclarationChildOfTheScope(Declaration candidateDeclaration, Declaration scopingDeclaration)
31+
{
32+
return scopingDeclaration == candidateDeclaration.ParentDeclaration;
33+
}
34+
35+
private static bool IsModuleLevelDeclarationOfTheScope(Declaration candidateDeclaration, Declaration scopingDeclaration)
36+
{
37+
if (candidateDeclaration.ParentDeclaration == null)
38+
{
39+
return false;
40+
}
41+
return candidateDeclaration.ComponentName == scopingDeclaration.ComponentName
42+
&& !IsDeclaredWithinMethodOrProperty(candidateDeclaration.ParentDeclaration.Context);
43+
}
44+
45+
private static bool IsProjectGlobalDeclaration(Declaration candidateDeclaration, Declaration scopingDeclaration)
46+
{
47+
return candidateDeclaration.ProjectName == scopingDeclaration.ProjectName
48+
&& !(candidateDeclaration.ParentScopeDeclaration is ClassModuleDeclaration)
49+
&& (candidateDeclaration.Accessibility == Accessibility.Public
50+
|| ((candidateDeclaration.Accessibility == Accessibility.Implicit)
51+
&& (candidateDeclaration.ParentScopeDeclaration is ProceduralModuleDeclaration)));
52+
}
53+
54+
private static bool IsDeclaredWithinMethodOrProperty(RuleContext procedureContextCandidate)
55+
{
56+
if (procedureContextCandidate == null) { return false; }
57+
58+
return (procedureContextCandidate is VBAParser.SubStmtContext)
59+
|| (procedureContextCandidate is VBAParser.FunctionStmtContext)
60+
|| (procedureContextCandidate is VBAParser.PropertyLetStmtContext)
61+
|| (procedureContextCandidate is VBAParser.PropertyGetStmtContext)
62+
|| (procedureContextCandidate is VBAParser.PropertySetStmtContext);
63+
}
64+
}
65+
}

RetailCoder.VBE/Refactorings/Rename/RenameRefactoring.cs

Lines changed: 4 additions & 63 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,8 @@
1414
using Rubberduck.VBEditor;
1515
using Rubberduck.VBEditor.SafeComWrappers;
1616
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
17+
using System.Collections.Generic;
18+
using Rubberduck.Inspections;
1719

1820
namespace Rubberduck.Refactorings.Rename
1921
{
@@ -92,68 +94,6 @@ public void Refactor(Declaration target)
9294
pane.Selection = oldSelection;
9395
}
9496
}
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-
15797
private static readonly DeclarationType[] ModuleDeclarationTypes =
15898
{
15999
DeclarationType.ClassModule,
@@ -162,7 +102,8 @@ private Declaration FindDeclarationForIdentifier()
162102

163103
private void Rename()
164104
{
165-
var declaration = FindDeclarationForIdentifier();
105+
var declaration = AccessibilityEvaluator.GetDeclarationsAccessibleToScope(_model.Target, _model.Declarations)
106+
.Where(d => d.IdentifierName == _model.NewName).FirstOrDefault();
166107
if (declaration != null)
167108
{
168109
var message = string.Format(RubberduckUI.RenameDialog_ConflictingNames, _model.NewName,

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -341,6 +341,7 @@
341341
<Compile Include="Common\WinAPI\WindowLongFlags.cs" />
342342
<Compile Include="Common\WindowsOperatingSystem.cs" />
343343
<Compile Include="Common\UndocumentedAttribute.cs" />
344+
<Compile Include="Inspections\AccessibilityEvaluator.cs" />
344345
<Compile Include="Inspections\ApplicationWorksheetFunctionInspection.cs" />
345346
<Compile Include="Inspections\HostSpecificExpressionInspection.cs" />
346347
<Compile Include="Inspections\HungarianNotationInspection.cs" />

RubberduckTests/Refactoring/RenameTests.cs

Lines changed: 127 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,74 @@ 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+
bool msgboxShowWasInvoked = true; // == failing condition
73+
try
74+
{
75+
//Throws an exception if Show() was NOT called => this is the successful behavior
76+
msgbox.Verify(m => m.Show(It.IsAny<string>(), It.IsAny<string>(), MessageBoxButtons.YesNo, It.IsAny<MessageBoxIcon>()));
77+
msgboxShowWasInvoked = true; //this line executed if the MessageBox is presented to the user
78+
}
79+
catch (MockException)
80+
{
81+
msgboxShowWasInvoked = false;
82+
}
83+
catch
84+
{
85+
throw;
86+
}
87+
Assert.IsFalse(msgboxShowWasInvoked, "RenameRefactoring found a conflicting declaration where none exists.");
88+
}
89+
90+
2391
[TestMethod]
2492
public void RenameRefactoring_RenameSub()
2593
{
@@ -1421,5 +1489,64 @@ private static Mock<IRefactoringPresenterFactory<IRenamePresenter>> SetupFactory
14211489
}
14221490

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

0 commit comments

Comments
 (0)