Skip to content

Commit

Permalink
Merge pull request #704 from Hosch250/next
Browse files Browse the repository at this point in the history
Fix bugs, more tests
  • Loading branch information
rubberduck203 committed Jul 10, 2015
2 parents d9c2b1c + 12c15bd commit 38ac435
Show file tree
Hide file tree
Showing 12 changed files with 1,831 additions and 167 deletions.
2 changes: 1 addition & 1 deletion RetailCoder.VBE/Inspections/ParameterNotUsedInspection.cs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ public IEnumerable<CodeInspectionResultBase> GetInspectionResults(VBProjectParse
var quickFixRefactoring =
new RemoveParametersRefactoring(
new RemoveParametersPresenterFactory(new ActiveCodePaneEditor(parseResult.Project.VBE),
new RemoveParametersDialog(), parseResult));
new RemoveParametersDialog(), parseResult, new RubberduckMessageBox()));

var issues = from issue in unused.Where(parameter => !IsInterfaceMemberParameter(parameter, interfaceMemberScopes))
let isInterfaceImplementationMember = IsInterfaceMemberImplementationParameter(issue, interfaceImplementationMemberScopes)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -19,10 +19,13 @@ public class RemoveParametersModel
public Declaration TargetDeclaration { get; private set; }
public List<Parameter> Parameters { get; set; }

public RemoveParametersModel(VBProjectParseResult parseResult, QualifiedSelection selection)
private readonly IMessageBox _messageBox;

public RemoveParametersModel(VBProjectParseResult parseResult, QualifiedSelection selection, IMessageBox messageBox)
{
_parseResult = parseResult;
_declarations = parseResult.Declarations;
_messageBox = messageBox;

AcquireTarget(selection);

Expand All @@ -39,10 +42,12 @@ private void AcquireTarget(QualifiedSelection selection)

private void LoadParameters()
{
if (TargetDeclaration == null) { return; }

Parameters.Clear();

var index = 0;
Parameters = GetParameters(TargetDeclaration).Select(arg => new Parameter(arg, index++)).ToList();
Parameters = GetParameters().Select(arg => new Parameter(arg, index++)).ToList();

if (TargetDeclaration.DeclarationType == DeclarationType.PropertyLet ||
TargetDeclaration.DeclarationType == DeclarationType.PropertySet)
Expand All @@ -51,17 +56,18 @@ private void LoadParameters()
}
}

private IEnumerable<Declaration> GetParameters(Declaration method)
private IEnumerable<Declaration> GetParameters()
{
var targetSelection = new Selection(TargetDeclaration.Context.Start.Line,
TargetDeclaration.Context.Start.Column,
TargetDeclaration.Context.Stop.Line,
TargetDeclaration.Context.Stop.Column);

return Declarations.Items
.Where(d => d.DeclarationType == DeclarationType.Parameter
&& d.ComponentName == method.ComponentName
&& d.Project.Equals(method.Project)
&& method.Context.GetSelection().Contains(
new Selection(d.Selection.StartLine,
d.Selection.StartColumn,
d.Selection.EndLine,
d.Selection.EndColumn)))
&& d.ComponentName == TargetDeclaration.ComponentName
&& d.Project.Equals(TargetDeclaration.Project)
&& targetSelection.Contains(d.Selection))
.OrderBy(item => item.Selection.StartLine)
.ThenBy(item => item.Selection.StartColumn);
}
Expand All @@ -88,12 +94,14 @@ private Declaration PromptIfTargetImplementsInterface()
var interfaceMember = Declarations.FindInterfaceMember(interfaceImplementation);
var message = string.Format(RubberduckUI.Refactoring_TargetIsInterfaceMemberImplementation, declaration.IdentifierName, interfaceMember.ComponentName, interfaceMember.IdentifierName);

var confirm = MessageBox.Show(message, RubberduckUI.ReorderParamsDialog_TitleText, MessageBoxButtons.YesNo, MessageBoxIcon.Exclamation);
var confirm = _messageBox.Show(message, RubberduckUI.ReorderParamsDialog_TitleText, MessageBoxButtons.YesNo, MessageBoxIcon.Exclamation);
return confirm == DialogResult.No ? null : interfaceMember;
}

private Declaration GetGetter()
{
if (TargetDeclaration == null) { return null; }

if (TargetDeclaration.DeclarationType != DeclarationType.PropertyLet &&
TargetDeclaration.DeclarationType != DeclarationType.PropertySet)
{
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -12,19 +12,23 @@ public class RemoveParametersPresenter : IRemoveParametersPresenter
{
private readonly IRemoveParametersView _view;
private readonly RemoveParametersModel _model;
private readonly IMessageBox _messageBox;

public RemoveParametersPresenter(IRemoveParametersView view, RemoveParametersModel model)
public RemoveParametersPresenter(IRemoveParametersView view, RemoveParametersModel model, IMessageBox messageBox)
{
_view = view;
_model = model;
_messageBox = messageBox;
}

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

if (_model.Parameters.Count == 0)
{
var message = string.Format(RubberduckUI.RemovePresenter_NoParametersError, _model.TargetDeclaration.IdentifierName);
MessageBox.Show(message, RubberduckUI.RemoveParamsDialog_TitleText, MessageBoxButtons.OK, MessageBoxIcon.Exclamation);
_messageBox.Show(message, RubberduckUI.RemoveParamsDialog_TitleText, MessageBoxButtons.OK, MessageBoxIcon.Exclamation);
return null;
}

Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
using Rubberduck.Parsing;
using Rubberduck.UI;
using Rubberduck.VBEditor;

namespace Rubberduck.Refactorings.RemoveParameters
Expand All @@ -8,13 +9,15 @@ public class RemoveParametersPresenterFactory : IRefactoringPresenterFactory<Rem
private readonly IActiveCodePaneEditor _editor;
private readonly IRemoveParametersView _view;
private readonly VBProjectParseResult _parseResult;
private readonly IMessageBox _messageBox;

public RemoveParametersPresenterFactory(IActiveCodePaneEditor editor, IRemoveParametersView view,
VBProjectParseResult parseResult)
VBProjectParseResult parseResult, IMessageBox messageBox)
{
_editor = editor;
_view = view;
_parseResult = parseResult;
_messageBox = messageBox;
}

public RemoveParametersPresenter Create()
Expand All @@ -25,8 +28,8 @@ public RemoveParametersPresenter Create()
return null;
}

var model = new RemoveParametersModel(_parseResult, selection.Value);
return new RemoveParametersPresenter(_view, model);
var model = new RemoveParametersModel(_parseResult, selection.Value, _messageBox);
return new RemoveParametersPresenter(_view, model, _messageBox);
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.UI;
using Rubberduck.VBA;
using Rubberduck.VBEditor;

Expand Down Expand Up @@ -57,7 +58,7 @@ public void Refactor(Declaration target)

public void QuickFix(VBProjectParseResult parseResult, QualifiedSelection selection)
{
_model = new RemoveParametersModel(parseResult, selection);
_model = new RemoveParametersModel(parseResult, selection, new RubberduckMessageBox());
var target = _model.Declarations.FindSelection(selection, new[] { DeclarationType.Parameter });

// ReSharper disable once PossibleUnintendedReferenceComparison
Expand All @@ -67,7 +68,7 @@ public void QuickFix(VBProjectParseResult parseResult, QualifiedSelection select

private void RemoveParameters()
{
if (_model.TargetDeclaration == null) { throw new NullReferenceException("Parameter is null."); }
if (_model.TargetDeclaration == null) { throw new NullReferenceException("Parameter is null"); }

AdjustReferences(_model.TargetDeclaration.References, _model.TargetDeclaration);
AdjustSignatures();
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -20,11 +20,14 @@ public class ReorderParametersModel

public Declaration TargetDeclaration { get; private set; }
public List<Parameter> Parameters { get; set; }

private readonly IMessageBox _messageBox;

public ReorderParametersModel(VBProjectParseResult parseResult, QualifiedSelection selection)
public ReorderParametersModel(VBProjectParseResult parseResult, QualifiedSelection selection, IMessageBox messageBox)
{
_parseResult = parseResult;
_declarations = parseResult.Declarations;
_messageBox = messageBox;

AcquireTaget(selection);

Expand Down Expand Up @@ -81,12 +84,17 @@ private Declaration PromptIfTargetImplementsInterface()
var interfaceMember = Declarations.FindInterfaceMember(interfaceImplementation);
var message = string.Format(RubberduckUI.Refactoring_TargetIsInterfaceMemberImplementation, declaration.IdentifierName, interfaceMember.ComponentName, interfaceMember.IdentifierName);

var confirm = MessageBox.Show(message, RubberduckUI.ReorderParamsDialog_TitleText, MessageBoxButtons.YesNo, MessageBoxIcon.Exclamation);
var confirm = _messageBox.Show(message, RubberduckUI.ReorderParamsDialog_TitleText, MessageBoxButtons.YesNo, MessageBoxIcon.Exclamation);
return confirm == DialogResult.No ? null : interfaceMember;
}

private Declaration GetGetter()
{
if (TargetDeclaration == null)
{
return null;
}

if (TargetDeclaration.DeclarationType != DeclarationType.PropertyLet &&
TargetDeclaration.DeclarationType != DeclarationType.PropertySet)
{
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -12,19 +12,23 @@ public class ReorderParametersPresenter : IReorderParametersPresenter
{
private readonly IReorderParametersView _view;
private readonly ReorderParametersModel _model;
private readonly IMessageBox _messageBox;

public ReorderParametersPresenter(IReorderParametersView view, ReorderParametersModel model)
public ReorderParametersPresenter(IReorderParametersView view, ReorderParametersModel model, IMessageBox messageBox)
{
_view = view;
_model = model;
_messageBox = messageBox;
}

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

if (_model.Parameters.Count < 2)
{
var message = string.Format(RubberduckUI.ReorderPresenter_LessThanTwoParametersError, _model.TargetDeclaration.IdentifierName);
MessageBox.Show(message, RubberduckUI.ReorderParamsDialog_TitleText, MessageBoxButtons.OK, MessageBoxIcon.Exclamation);
_messageBox.Show(message, RubberduckUI.ReorderParamsDialog_TitleText, MessageBoxButtons.OK, MessageBoxIcon.Exclamation);
return null;
}

Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
using Rubberduck.Parsing;
using Rubberduck.UI;
using Rubberduck.VBEditor;

namespace Rubberduck.Refactorings.ReorderParameters
Expand All @@ -8,13 +9,15 @@ public class ReorderParametersPresenterFactory : IRefactoringPresenterFactory<IR
private readonly IActiveCodePaneEditor _editor;
private readonly IReorderParametersView _view;
private readonly VBProjectParseResult _parseResult;
private readonly IMessageBox _messageBox;

public ReorderParametersPresenterFactory(IActiveCodePaneEditor editor, IReorderParametersView view,
VBProjectParseResult parseResult)
VBProjectParseResult parseResult, IMessageBox messageBox)
{
_editor = editor;
_view = view;
_parseResult = parseResult;
_messageBox = messageBox;
}

public IReorderParametersPresenter Create()
Expand All @@ -25,8 +28,8 @@ public IReorderParametersPresenter Create()
return null;
}

var model = new ReorderParametersModel(_parseResult, selection.Value);
return new ReorderParametersPresenter(_view, model);
var model = new ReorderParametersModel(_parseResult, selection.Value, _messageBox);
return new ReorderParametersPresenter(_view, model, _messageBox);
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -122,14 +122,6 @@ private void RewriteCall(VBAParser.ArgsCallContext paramList, CodeModule module)

if (parameterStringIndex <= -1) { continue; }

if (_model.Parameters.ElementAt(parameterIndex).Index >= paramNames.Count)
{
newContent = newContent.Insert(parameterStringIndex, " , ");
i--;
parameterIndex++;
continue;
}

var oldParameterString = paramNames.ElementAt(i);
var newParameterString = paramNames.ElementAt(_model.Parameters.ElementAt(parameterIndex).Index);
var beginningSub = newContent.Substring(0, parameterStringIndex);
Expand Down
4 changes: 2 additions & 2 deletions RetailCoder.VBE/UI/RefactorMenu.cs
Original file line number Diff line number Diff line change
Expand Up @@ -460,7 +460,7 @@ private void ReorderParameters(QualifiedSelection selection)

using (var view = new ReorderParametersDialog())
{
var factory = new ReorderParametersPresenterFactory(_editor, view, result);
var factory = new ReorderParametersPresenterFactory(_editor, view, result, new RubberduckMessageBox());
var refactoring = new ReorderParametersRefactoring(factory, new RubberduckMessageBox());
refactoring.Refactor(selection);
}
Expand All @@ -473,7 +473,7 @@ private void RemoveParameter(QualifiedSelection selection)

using (var view = new RemoveParametersDialog())
{
var factory = new RemoveParametersPresenterFactory(_editor, view, result);
var factory = new RemoveParametersPresenterFactory(_editor, view, result, new RubberduckMessageBox());
var refactoring = new RemoveParametersRefactoring(factory);
refactoring.Refactor(selection);
}
Expand Down

0 comments on commit 38ac435

Please sign in to comment.