Skip to content

Commit

Permalink
all tests pass (ExtractMethod tests still disabled)
Browse files Browse the repository at this point in the history
  • Loading branch information
retailcoder committed Oct 5, 2016
1 parent 5ab9a74 commit 8d50e17
Show file tree
Hide file tree
Showing 72 changed files with 562 additions and 646 deletions.
Original file line number Diff line number Diff line change
@@ -1,7 +1,5 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.VBEditor.DisposableWrappers;
using Rubberduck.VBEditor.DisposableWrappers.VBA;
using Rubberduck.VBEditor.Extensions;

namespace Rubberduck.Refactorings.EncapsulateField
{
Expand All @@ -20,7 +18,7 @@ public EncapsulateFieldPresenterFactory(VBE vbe, RubberduckParserState state, IE

public EncapsulateFieldPresenter Create()
{
var selection = _vbe.ActiveCodePane.CodeModule.GetSelection();
var selection = _vbe.ActiveCodePane.GetQualifiedSelection();
if (!selection.HasValue)
{
return null;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ public void Refactor()
QualifiedSelection? oldSelection = null;
if (_vbe.ActiveCodePane != null)
{
oldSelection = _vbe.ActiveCodePane.CodeModule.GetSelection();
oldSelection = _vbe.ActiveCodePane.CodeModule.GetQualifiedSelection();
}

AddProperty();
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ public ExtractInterfaceModel Show()
}

_view.ComponentNames =
_model.TargetDeclaration.Project.VBComponents.Cast<VBComponent>().Select(c => c.Name).ToList();
_model.TargetDeclaration.Project.VBComponents.Select(c => c.Name).ToList();
_view.InterfaceName = _model.InterfaceName;
_view.Members = _model.Members;

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,7 @@ public void Refactor()
{
var module = pane.CodeModule;
{
oldSelection = module.GetSelection();
oldSelection = module.GetQualifiedSelection();
}
}
else
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ public void Refactor()
}
*/
var qualifiedSelection = _codeModule.GetSelection();
var qualifiedSelection = _codeModule.GetQualifiedSelection();
if (!qualifiedSelection.HasValue)
{
return;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@ public void Refactor(QualifiedSelection selection)
QualifiedSelection? oldSelection = null;
if (_vbe.ActiveCodePane != null)
{
oldSelection = _vbe.ActiveCodePane.CodeModule.GetSelection();
oldSelection = _vbe.ActiveCodePane.CodeModule.GetQualifiedSelection();
}

ImplementMissingMembers();
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ private void PromoteVariable(Declaration target)
QualifiedSelection? oldSelection = null;
if (_vbe.ActiveCodePane != null)
{
oldSelection = _vbe.ActiveCodePane.CodeModule.GetSelection();
oldSelection = _vbe.ActiveCodePane.CodeModule.GetQualifiedSelection();
}

RemoveVariable(target);
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ public void Refactor()
var pane = _vbe.ActiveCodePane;
var module = pane.CodeModule;
{
var selection = module.GetSelection();
var selection = module.GetQualifiedSelection();
if (!selection.HasValue)
{
_messageBox.Show(RubberduckUI.PromoteVariable_InvalidSelection, RubberduckUI.IntroduceParameter_Caption,
Expand Down Expand Up @@ -105,7 +105,7 @@ private void PromoteVariable(Declaration target)
{
if (_vbe.ActiveCodePane != null)
{
oldSelection = module.GetSelection();
oldSelection = module.GetQualifiedSelection();
}

RemoveVariable(target);
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ public MoveCloserToUsageRefactoring(VBE vbe, RubberduckParserState state, IMessa

public void Refactor()
{
var qualifiedSelection = _vbe.ActiveCodePane.CodeModule.GetSelection();
var qualifiedSelection = _vbe.ActiveCodePane.CodeModule.GetQualifiedSelection();
if (qualifiedSelection != null)
{
Refactor(_declarations.FindVariable(qualifiedSelection.Value));
Expand Down Expand Up @@ -108,7 +108,7 @@ private void MoveCloserToUsage()
{
if (!module.IsWrappingNullReference)
{
oldSelection = module.GetSelection();
oldSelection = module.GetQualifiedSelection();
}

// it doesn't make sense to do it backwards, but we need to work from the bottom up so our selections are accurate
Expand All @@ -134,7 +134,7 @@ private void _state_StateChanged(object sender, ParserStateEventArgs e)
{
if (!module.IsWrappingNullReference)
{
oldSelection = module.GetSelection();
oldSelection = module.GetQualifiedSelection();
}

var newTarget = _state.AllUserDeclarations.FirstOrDefault(
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,10 @@ public RemoveParametersPresenter(IRemoveParametersDialog view, RemoveParametersM

public RemoveParametersModel Show()
{
if (_model.TargetDeclaration == null) { return null; }
if (_model.TargetDeclaration == null)
{
return null;
}

if (_model.Parameters.Count == 0)
{
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ public void Refactor()
{
if (!module.IsWrappingNullReference)
{
oldSelection = module.GetSelection();
oldSelection = module.GetQualifiedSelection();
}

RemoveParameters();
Expand Down
4 changes: 1 addition & 3 deletions RetailCoder.VBE/Refactorings/Rename/RenameRefactoring.cs
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ public void Refactor()
{
if (!pane.IsWrappingNullReference)
{
oldSelection = module.GetSelection();
oldSelection = module.GetQualifiedSelection();
}

if (_model != null && _model.Declarations != null)
Expand All @@ -56,7 +56,6 @@ public void Refactor()
if (oldSelection.HasValue)
{
pane.SetSelection(oldSelection.Value.Selection);
pane.ForceFocus();
}
}
}
Expand Down Expand Up @@ -93,7 +92,6 @@ public void Refactor(Declaration target)
}

pane.SetSelection(oldSelection);
pane.ForceFocus();
}
}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ public void Refactor()
QualifiedSelection? oldSelection;
var module = pane.CodeModule;
{
oldSelection = module.GetSelection();
oldSelection = module.GetQualifiedSelection();
}

AdjustReferences(_model.TargetDeclaration.References);
Expand All @@ -58,7 +58,6 @@ public void Refactor()
if (oldSelection.HasValue)
{
pane.SetSelection(oldSelection.Value.Selection);
pane.ForceFocus();
}
}

Expand Down
1 change: 0 additions & 1 deletion RetailCoder.VBE/UI/Command/NavigateCommand.cs
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,6 @@ protected override void ExecuteImpl(object parameter)
var selection = param.Selection;

pane.SetSelection(selection.StartLine, selection.StartColumn, selection.EndLine, selection.EndColumn);
pane.ForceFocus();
}
catch (COMException)
{
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Refactorings.ExtractInterface;
using Rubberduck.UI.Refactorings;
using Rubberduck.VBEditor.DisposableWrappers;
using Rubberduck.VBEditor.DisposableWrappers.VBA;
using Rubberduck.VBEditor.Extensions;

namespace Rubberduck.UI.Command.Refactorings
{
Expand Down
96 changes: 95 additions & 1 deletion Rubberduck.VBEEditor/DisposableWrappers/VBA/CodeModule.cs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
using System;
using System.Diagnostics.CodeAnalysis;
using System.Runtime.InteropServices;
using System.Security.Cryptography;
using System.Text;
Expand All @@ -7,6 +8,7 @@

namespace Rubberduck.VBEditor.DisposableWrappers.VBA
{
[SuppressMessage("ReSharper", "UseIndexedProperty")]
public class CodeModule : SafeComWrapper<Microsoft.Vbe.Interop.CodeModule>, IEquatable<CodeModule>
{
public CodeModule(Microsoft.Vbe.Interop.CodeModule comObject)
Expand Down Expand Up @@ -50,9 +52,101 @@ public string GetLines(int startLine, int count)
return InvokeResult(() => ComObject.get_Lines(startLine, count));
}

/// <summary>
/// Returns the lines containing the selection.
/// </summary>
/// <param name="selection"></param>
/// <returns></returns>
public string GetLines(Selection selection)
{
return GetLines(selection.StartLine, selection.LineCount);
}

/// <summary>
/// Deletes the lines containing the selection.
/// </summary>
/// <param name="selection"></param>
public void DeleteLines(Selection selection)
{
DeleteLines(selection.StartLine, selection.LineCount);
}

public QualifiedSelection? GetQualifiedSelection()
{
if (IsWrappingNullReference || CodePane.IsWrappingNullReference)
{
return null;
}
return CodePane.GetQualifiedSelection();
}

public string Content()
{
return GetLines(1, CountOfLines);
return InvokeResult(() => ComObject.CountOfLines == 0 ? string.Empty : GetLines(1, CountOfLines));
}

public void Clear()
{
Invoke(() => ComObject.DeleteLines(1, CountOfLines));
}

/// <summary>
/// Gets an array of strings where each element is a line of code in the Module,
/// with line numbers stripped and any other pre-processing that needs to be done.
/// </summary>
public string[] GetSanitizedCode()
{
var lines = CountOfLines;
if (lines == 0)
{
return new string[] { };
}

var code = GetLines(1, lines).Replace("\r", string.Empty).Split('\n');

StripLineNumbers(code);
return code;
}

private void StripLineNumbers(string[] lines)
{
var continuing = false;
for (var line = 0; line < lines.Length; line++)
{
var code = lines[line];
int? lineNumber;
if (!continuing && HasNumberedLine(code, out lineNumber))
{
var lineNumberLength = lineNumber.ToString().Length;
if (lines[line].Length > lineNumberLength)
{
// replace line number with as many spaces as characters taken, to avoid shifting the tokens
lines[line] = new string(' ', lineNumberLength) + code.Substring(lineNumber.ToString().Length + 1);
}
}

continuing = code.EndsWith("_");
}
}

private bool HasNumberedLine(string codeLine, out int? lineNumber)
{
lineNumber = null;

if (string.IsNullOrWhiteSpace(codeLine.Trim()))
{
return false;
}

int line;
var firstToken = codeLine.TrimStart().Split(' ')[0];
if (int.TryParse(firstToken, out line))
{
lineNumber = line;
return true;
}

return false;
}

private string _previousContentHash;
Expand Down
49 changes: 46 additions & 3 deletions Rubberduck.VBEEditor/DisposableWrappers/VBA/CodePane.cs
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,13 @@ public Selection GetSelection()
int endLine;
int endColumn;
ComObject.GetSelection(out startLine, out startColumn, out endLine, out endColumn);
if (endLine > startLine && endColumn == 1)
{
endLine -= 1;
endColumn = CodeModule.GetLines(endLine, 1).Length;
}
return new Selection(startLine, startColumn, endLine, endColumn);
});
}
Expand All @@ -67,15 +74,51 @@ public Selection GetSelection()
}
}

public QualifiedSelection? GetQualifiedSelection()
{
if (IsWrappingNullReference)
{
return null;
}

var selection = GetSelection();
if (selection.IsEmpty())
{
return null;
}

var component = new VBComponent(CodeModule.Parent.ComObject);
var moduleName = new QualifiedModuleName(component);
return new QualifiedSelection(moduleName, selection);
}

public void SetSelection(int startLine, int startColumn, int endLine, int endColumn)
{
Invoke(() => ComObject.SetSelection(startLine, startColumn, endLine, endColumn));
ForceFocus();
}

public void SetSelection(Selection selection)
{
Invoke(() => ComObject.SetSelection(selection.StartLine, selection.StartColumn, selection.EndLine, selection.EndColumn));
this.ForceFocus();
SetSelection(selection.StartLine, selection.StartColumn, selection.EndLine, selection.EndColumn);
}

private void ForceFocus()
{
Show();

var window = VBE.MainWindow;
var mainWindowHandle = window.Handle();
var caption = window.Caption;
var childWindowFinder = new NativeMethods.ChildWindowFinder(caption);

NativeMethods.EnumChildWindows(mainWindowHandle, childWindowFinder.EnumWindowsProcToChildWindowByCaption);
var handle = childWindowFinder.ResultHandle;

if (handle != IntPtr.Zero)
{
NativeMethods.ActivateWindow(handle, mainWindowHandle);
}
}

public void Show()
Expand All @@ -87,7 +130,7 @@ public override void Release()
{
if (!IsWrappingNullReference)
{
Window.Release();
//Window.Release(); window is released by VBE.Windows
Marshal.ReleaseComObject(ComObject);
}
}
Expand Down

0 comments on commit 8d50e17

Please sign in to comment.