Skip to content

Commit a93fce9

Browse files
authored
Merge pull request #2758 from comintern/next
Fix statement separator handling in MoveCloserToUsageRefactoring. Closes #2753
2 parents 359cbcf + aa59e31 commit a93fce9

File tree

5 files changed

+120
-11
lines changed

5 files changed

+120
-11
lines changed

RetailCoder.VBE/Refactorings/MoveCloserToUsage/MoveCloserToUsageRefactoring.cs

Lines changed: 13 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Linq;
4+
using System.Text.RegularExpressions;
45
using System.Windows.Forms;
56
using Rubberduck.Common;
67
using Rubberduck.Parsing;
@@ -170,7 +171,8 @@ private void InsertDeclaration()
170171

171172
var newLinesWithoutStringLiterals = newLines.StripStringLiterals();
172173

173-
var lastIndexOfColon = newLinesWithoutStringLiterals.LastIndexOf(':');
174+
var lastIndexOfColon = GetIndexOfLastStatementSeparator(newLinesWithoutStringLiterals);
175+
// ReSharper disable once StringLastIndexOfIsCultureSpecific.1
174176
while (lastIndexOfColon != -1)
175177
{
176178
var numberOfCharsToRemove = lastIndexOfColon == newLines.Length - 1 || newLines[lastIndexOfColon + 1] != ' '
@@ -185,14 +187,21 @@ private void InsertDeclaration()
185187
.Remove(lastIndexOfColon, numberOfCharsToRemove)
186188
.Insert(lastIndexOfColon, Environment.NewLine);
187189

188-
lastIndexOfColon = newLinesWithoutStringLiterals.LastIndexOf(':');
190+
lastIndexOfColon = GetIndexOfLastStatementSeparator(newLinesWithoutStringLiterals);
189191
}
190192

191193
module.DeleteLines(beginningOfInstructionSelection.StartLine, beginningOfInstructionSelection.LineCount);
192194
module.InsertLines(beginningOfInstructionSelection.StartLine, newLines);
193195
}
194196
}
195197

198+
private static readonly Regex StatementSeparatorRegex = new Regex(":[^=]", RegexOptions.RightToLeft);
199+
private static int GetIndexOfLastStatementSeparator(string input)
200+
{
201+
var matches = StatementSeparatorRegex.Matches(input);
202+
return matches.Count == 0 ? -1 : matches[0].Index;
203+
}
204+
196205
private Selection GetBeginningOfInstructionSelection(IdentifierReference reference)
197206
{
198207
var referenceSelection = reference.Selection;
@@ -201,7 +210,7 @@ private Selection GetBeginningOfInstructionSelection(IdentifierReference referen
201210
var currentLine = referenceSelection.StartLine;
202211

203212
var codeLine = module.GetLines(currentLine, 1).StripStringLiterals();
204-
while (codeLine.Remove(referenceSelection.StartColumn).LastIndexOf(':') == -1)
213+
while (GetIndexOfLastStatementSeparator(codeLine.Remove(referenceSelection.StartColumn)) == -1)
205214
{
206215
codeLine = module.GetLines(--currentLine, 1).StripStringLiterals();
207216
if (!codeLine.EndsWith(" _"))
@@ -210,7 +219,7 @@ private Selection GetBeginningOfInstructionSelection(IdentifierReference referen
210219
}
211220
}
212221

213-
var index = codeLine.Remove(referenceSelection.StartColumn).LastIndexOf(':') + 1;
222+
var index = GetIndexOfLastStatementSeparator(codeLine.Remove(referenceSelection.StartColumn)) + 1;
214223
return new Selection(currentLine, index, currentLine, index);
215224
}
216225
}

RetailCoder.VBE/UI/SelectionChangeService.cs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -81,8 +81,7 @@ private void DispatchSelectionChanged(DeclarationChangedEventArgs eventArgs)
8181
}
8282
SelectionChanged.Invoke(null, eventArgs);
8383
}
84-
85-
84+
8685
private void DispatchSelectedDeclaration(DeclarationChangedEventArgs eventArgs)
8786
{
8887
DispatchSelectionChanged(eventArgs);
@@ -111,7 +110,7 @@ private void DispatchSelectedDesignerDeclaration(IVBComponent component)
111110
{
112111
var name = component.SelectedControls.First().Name;
113112
var control =
114-
_parser.State.AllUserDeclarations.SingleOrDefault(decl =>
113+
_parser.State.DeclarationFinder.UserDeclarations(DeclarationType.Control).SingleOrDefault(decl =>
115114
decl.IdentifierName.Equals(name) &&
116115
decl.ParentDeclaration.IdentifierName.Equals(component.Name) &&
117116
decl.ProjectId.Equals(component.ParentProject.ProjectId));
@@ -120,7 +119,7 @@ private void DispatchSelectedDesignerDeclaration(IVBComponent component)
120119
return;
121120
}
122121
var form =
123-
_parser.State.AllUserDeclarations.SingleOrDefault(decl =>
122+
_parser.State.DeclarationFinder.UserDeclarations(DeclarationType.UserForm).SingleOrDefault(decl =>
124123
decl.IdentifierName.Equals(component.Name) &&
125124
decl.ProjectId.Equals(component.ParentProject.ProjectId));
126125

@@ -144,7 +143,7 @@ private void DispatchSelectedProjectNodeDeclaration(IVBComponent component)
144143
}
145144
else if (component != null)
146145
{
147-
//The user might have selected the project node in Project Explorer. If they've chosen a folder, we'll return the project anyway.
146+
148147
var module =
149148
_parser.State.AllUserDeclarations.SingleOrDefault(
150149
decl => decl.DeclarationType.HasFlag(DeclarationType.Module) &&

Rubberduck.VBEEditor/WindowsApi/CodePaneSubclass.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ internal CodePaneSubclass(IntPtr hwnd, ICodePane pane) : base(hwnd)
1919
protected override void DispatchFocusEvent(FocusType type)
2020
{
2121
var window = VBENativeServices.GetWindowInfoFromHwnd(Hwnd);
22-
if (window == null)
22+
if (!window.HasValue)
2323
{
2424
return;
2525
}

Rubberduck.VBEEditor/WindowsApi/FocusSource.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System;
22
using Rubberduck.Common.WinAPI;
33
using Rubberduck.VBEditor.Events;
4+
using Rubberduck.VBEditor.SafeComWrappers.MSForms;
45

56
namespace Rubberduck.VBEditor.WindowsApi
67
{
@@ -20,7 +21,7 @@ protected void OnFocusChange(WindowChangedEventArgs eventArgs)
2021
protected virtual void DispatchFocusEvent(FocusType type)
2122
{
2223
var window = VBENativeServices.GetWindowInfoFromHwnd(Hwnd);
23-
if (window == null)
24+
if (!window.HasValue)
2425
{
2526
return;
2627
}

RubberduckTests/Refactoring/MoveCloserToUsageTests.cs

Lines changed: 100 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -849,6 +849,106 @@ End Sub
849849
Assert.AreEqual(expectedCode, module.Content());
850850
}
851851

852+
[TestMethod]
853+
public void MoveCloserToUsageRefactoring_WorksWithNamedParameters()
854+
{
855+
//Input
856+
const string inputCode =
857+
@"Private foo As Long
858+
859+
Public Sub Test()
860+
SomeSub someParam:=foo
861+
End Sub
862+
863+
Public Sub SomeSub(ByVal someParam As Long)
864+
Debug.Print someParam
865+
End Sub";
866+
867+
var selection = new Selection(1, 1, 1, 1);
868+
const string expectedCode =
869+
@"
870+
Public Sub Test()
871+
872+
Dim foo As Long
873+
SomeSub someParam:=foo
874+
End Sub
875+
876+
Public Sub SomeSub(ByVal someParam As Long)
877+
Debug.Print someParam
878+
End Sub";
879+
880+
//Arrange
881+
var builder = new MockVbeBuilder();
882+
IVBComponent component;
883+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component, selection);
884+
var project = vbe.Object.VBProjects[0];
885+
var module = project.VBComponents[0].CodeModule;
886+
var mockHost = new Mock<IHostApplication>();
887+
mockHost.SetupAllProperties();
888+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
889+
890+
parser.Parse(new CancellationTokenSource());
891+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
892+
893+
var qualifiedSelection = new QualifiedSelection(new QualifiedModuleName(component), selection);
894+
895+
//Act
896+
var refactoring = new MoveCloserToUsageRefactoring(vbe.Object, parser.State, null);
897+
refactoring.Refactor(qualifiedSelection);
898+
899+
//Assert
900+
Assert.AreEqual(expectedCode, module.Content());
901+
}
902+
903+
[TestMethod]
904+
public void MoveCloserToUsageRefactoring_WorksWithNamedParametersAndStatementSeparaters()
905+
{
906+
//Input
907+
const string inputCode =
908+
@"Private foo As Long
909+
910+
Public Sub Test(): SomeSub someParam:=foo: End Sub
911+
912+
Public Sub SomeSub(ByVal someParam As Long)
913+
Debug.Print someParam
914+
End Sub";
915+
916+
var selection = new Selection(1, 1, 1, 1);
917+
const string expectedCode =
918+
@"
919+
Public Sub Test()
920+
Dim foo As Long
921+
922+
SomeSub someParam:=foo
923+
End Sub
924+
925+
Public Sub SomeSub(ByVal someParam As Long)
926+
Debug.Print someParam
927+
End Sub";
928+
929+
//Arrange
930+
var builder = new MockVbeBuilder();
931+
IVBComponent component;
932+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component, selection);
933+
var project = vbe.Object.VBProjects[0];
934+
var module = project.VBComponents[0].CodeModule;
935+
var mockHost = new Mock<IHostApplication>();
936+
mockHost.SetupAllProperties();
937+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
938+
939+
parser.Parse(new CancellationTokenSource());
940+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
941+
942+
var qualifiedSelection = new QualifiedSelection(new QualifiedModuleName(component), selection);
943+
944+
//Act
945+
var refactoring = new MoveCloserToUsageRefactoring(vbe.Object, parser.State, null);
946+
refactoring.Refactor(qualifiedSelection);
947+
948+
//Assert
949+
Assert.AreEqual(expectedCode, module.Content());
950+
}
951+
852952
[TestMethod]
853953
public void IntroduceFieldRefactoring_PassInTarget_Nonvariable()
854954
{

0 commit comments

Comments
 (0)