Skip to content

Commit

Permalink
Merge pull request #694 from ckuhn203/next
Browse files Browse the repository at this point in the history
ExtractMethodRefactoring test harness
  • Loading branch information
retailcoder committed Jul 8, 2015
2 parents 32ecb80 + 3d09a20 commit d3a6a0d
Show file tree
Hide file tree
Showing 10 changed files with 179 additions and 125 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,12 @@

namespace Rubberduck.Refactorings.ExtractMethod
{
public class ExtractMethodPresenter
public interface IExtractMethodPresenter
{
ExtractMethodModel Show();
}

public class ExtractMethodPresenter : IExtractMethodPresenter
{
private readonly IExtractMethodDialog _view;
private readonly ExtractMethodModel _model;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@

namespace Rubberduck.Refactorings.ExtractMethod
{
public class ExtractMethodPresenterFactory : IRefactoringPresenterFactory<ExtractMethodPresenter>
public class ExtractMethodPresenterFactory : IRefactoringPresenterFactory<IExtractMethodPresenter>
{
private readonly IActiveCodePaneEditor _editor;
private readonly Declarations _declarations;
Expand All @@ -16,7 +16,7 @@ public ExtractMethodPresenterFactory(IActiveCodePaneEditor editor, Declarations
_declarations = declarations;
}

public ExtractMethodPresenter Create()
public IExtractMethodPresenter Create()
{
var selection = _editor.GetSelection();
if (selection == null)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -15,9 +15,9 @@ namespace Rubberduck.Refactorings.ExtractMethod
public class ExtractMethodRefactoring : IRefactoring
{
private readonly IActiveCodePaneEditor _editor;
private readonly IRefactoringPresenterFactory<ExtractMethodPresenter> _factory;
private readonly IRefactoringPresenterFactory<IExtractMethodPresenter> _factory;

public ExtractMethodRefactoring(IRefactoringPresenterFactory<ExtractMethodPresenter> factory, IActiveCodePaneEditor editor)
public ExtractMethodRefactoring(IRefactoringPresenterFactory<IExtractMethodPresenter> factory, IActiveCodePaneEditor editor)
{
_factory = factory;
_editor = editor;
Expand Down
2 changes: 2 additions & 0 deletions RetailCoder.VBE/UI/CodeExplorer/CodeExplorerWindow.cs
Original file line number Diff line number Diff line change
@@ -1,11 +1,13 @@
using System;
using System.Diagnostics.CodeAnalysis;
using System.Windows.Forms;
using Microsoft.Vbe.Interop;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Properties;

namespace Rubberduck.UI.CodeExplorer
{
[ExcludeFromCodeCoverage]
public partial class CodeExplorerWindow : UserControl, IDockableUserControl
{
private const string ClassId = "C5318B59-172F-417C-88E3-B377CDA2D809";
Expand Down
10 changes: 8 additions & 2 deletions RubberduckTests/Mocks/MockFactory.cs
Original file line number Diff line number Diff line change
Expand Up @@ -103,10 +103,10 @@ internal static Mock<CodePane> CreateCodePaneMock(Mock<VBE> vbe, Mock<Window> wi
/// <returns></returns>
internal static Mock<CodeModule> CreateCodeModuleMock(string code)
{
var lines = code.Split(new [] { Environment.NewLine }, StringSplitOptions.None);
var lines = code.Split(new[] {Environment.NewLine}, StringSplitOptions.None).ToList();

var codeModule = new Mock<CodeModule>();
codeModule.SetupGet(c => c.CountOfLines).Returns(lines.Length);
codeModule.SetupGet(c => c.CountOfLines).Returns(lines.Count);

// ReSharper disable once UseIndexedProperty
// No R#, the indexed property breaks the expression. I tried that first.
Expand All @@ -115,6 +115,12 @@ internal static Mock<CodeModule> CreateCodeModuleMock(string code)

codeModule.Setup(m => m.ReplaceLine(It.IsAny<int>(), It.IsAny<string>()))
.Callback<int, string>((index, str) => lines[index - 1] = str);

codeModule.Setup(m => m.DeleteLines(It.IsAny<int>(), It.IsAny<int>()))
.Callback<int, int>((index, count) => lines.RemoveRange(index - 1, count));

codeModule.Setup(m => m.InsertLines(It.IsAny<int>(), It.IsAny<string>()))
.Callback<int, string>((index, newLine) => lines.Insert(index - 1, newLine));

return codeModule;
}
Expand Down
72 changes: 72 additions & 0 deletions RubberduckTests/Refactoring/ExtractMethodTests.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,72 @@
using System.Collections.Generic;
using Microsoft.VisualStudio.TestTools.UnitTesting;
using Moq;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Refactorings;
using Rubberduck.Refactorings.ExtractMethod;
using Rubberduck.VBEditor;
using Rubberduck.VBEditor.Extensions;

namespace RubberduckTests.Refactoring
{
[TestClass]
public class ExtractMethodTests : RefactoringTestBase
{
[TestMethod]
public void ExtractMethod_PrivateFunction()
{
const string inputCode = @"
Private Sub Foo()
Dim x As Integer
x = 1 + 2
End Sub";

const string expectedCode = @"
Private Sub Foo()
x = Bar()
End Sub
Private Function Bar() As Integer
Dim x As Integer
x = 1 + 2
Bar = x
End Function
";

SetupProject(inputCode);

var qualifiedSelection = GetQualifiedSelection(new Selection(4,1,4,20));

var parseResult = new RubberduckParser().Parse(Project.Object);

var editor = new ActiveCodePaneEditor(IDE.Object);

var model = new ExtractMethodModel(editor, parseResult.Declarations, qualifiedSelection);
model.Method.Accessibility = Accessibility.Private;
model.Method.MethodName = "Bar";
model.Method.ReturnValue = new ExtractedParameter("Integer", ExtractedParameter.PassedBy.ByVal, "x");
model.Method.Parameters = new List<ExtractedParameter>();

var factory = SetupFactory(model);

//act
var refactoring = new ExtractMethodRefactoring(factory.Object, editor);
refactoring.Refactor(qualifiedSelection);

//assert
Assert.AreEqual(expectedCode, Module.Object.Lines());
}

private static Mock<IRefactoringPresenterFactory<IExtractMethodPresenter>> SetupFactory(ExtractMethodModel model)
{
var presenter = new Mock<IExtractMethodPresenter>();
presenter.Setup(p => p.Show()).Returns(model);

var factory = new Mock<IRefactoringPresenterFactory<IExtractMethodPresenter>>();
factory.Setup(f => f.Create()).Returns(presenter.Object);
return factory;
}
}
}
57 changes: 57 additions & 0 deletions RubberduckTests/Refactoring/RefactoringTestBase.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,57 @@
using System.Collections.Generic;
using Microsoft.Vbe.Interop;
using Microsoft.VisualStudio.TestTools.UnitTesting;
using Moq;
using Rubberduck.VBEditor;
using RubberduckTests.Mocks;
using MockFactory = RubberduckTests.Mocks.MockFactory;

namespace RubberduckTests.Refactoring
{
public abstract class RefactoringTestBase
{
protected Mock<VBProject> Project;
protected Mock<VBComponent> Component;
protected Mock<CodeModule> Module;
protected Mock<VBE> IDE;

[TestCleanup]
public void CleanUp()
{
Project = null;
Component = null;
Module = null;
}

protected QualifiedSelection GetQualifiedSelection(Selection selection)
{
return new QualifiedSelection(new QualifiedModuleName(Component.Object), selection);
}

protected void SetupProject(string inputCode)
{
var window = MockFactory.CreateWindowMock(string.Empty);
var windows = new MockWindowsCollection(window.Object);

IDE = MockFactory.CreateVbeMock(windows);

var codePane = MockFactory.CreateCodePaneMock(IDE, window);

IDE.SetupGet(vbe => vbe.ActiveCodePane).Returns(codePane.Object);

Module = MockFactory.CreateCodeModuleMock(inputCode, codePane.Object);

codePane.SetupGet(p => p.CodeModule).Returns(Module.Object);

Project = MockFactory.CreateProjectMock("VBAProject", vbext_ProjectProtection.vbext_pp_none);

Component = MockFactory.CreateComponentMock("Module1", Module.Object, vbext_ComponentType.vbext_ct_StdModule);

var components = MockFactory.CreateComponentsMock(new List<VBComponent>() { Component.Object });
components.SetupGet(c => c.Parent).Returns(Project.Object);

Project.SetupGet(p => p.VBComponents).Returns(components.Object);
Component.SetupGet(c => c.Collection).Returns(components.Object);
}
}
}
Loading

0 comments on commit d3a6a0d

Please sign in to comment.