Skip to content
Closed
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
34 changes: 16 additions & 18 deletions RetailCoder.VBE/App.cs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
using System.Globalization;
using System.Windows.Forms;
using Microsoft.Vbe.Interop;
using Rubberduck.Navigations;
using Rubberduck.Inspections;
using Rubberduck.Parsing;
using Rubberduck.Parsing.VBA;
Expand All @@ -23,8 +24,9 @@ public class App : IDisposable
private IParserErrorsPresenter _parserErrorsPresenter;
private readonly IConfigurationLoader _configService = new ConfigurationLoader();
private readonly IActiveCodePaneEditor _editor;
private readonly IRubberduckCodePaneFactory _factory;
private readonly IRubberduckCodePaneFactory _codePaneFactory;
private readonly IRubberduckParser _parser;
private readonly INavigateImplementations _navigateImplementations;

private Configuration _config;
private RubberduckMenu _menu;
Expand All @@ -33,35 +35,31 @@ public class App : IDisposable
private bool _displayToolbar = false;
private Point _toolbarCoords = new Point(-1, -1);

public App(VBE vbe, AddIn addIn, IParserErrorsPresenter presenter, IRubberduckParser parser, IRubberduckCodePaneFactory factory, IActiveCodePaneEditor editor)
public App(VBE vbe, AddIn addIn, IParserErrorsPresenter presenter, IRubberduckParser parser, IRubberduckCodePaneFactory factory, IActiveCodePaneEditor editor, INavigateImplementations navigateImplementations)
{
_vbe = vbe;
_addIn = addIn;
_factory = factory;
_codePaneFactory = factory;
_parser = parser;
_navigateImplementations = navigateImplementations;

_parserErrorsPresenter = presenter;
_configService.SettingsChanged += _configService_SettingsChanged;

// todo: figure out why Ninject can't seem to resolve the VBE dependency to ActiveCodePaneEditor if it's in the VBEDitor assembly.
// could it be that the VBE type in the two assemblies is actually different?
// aren't the two assemblies using the exact same Microsoft.Vbe.Interop assemby?

_editor = editor; // */ new ActiveCodePaneEditor(vbe, _factory);
_editor = editor;

LoadConfig();

CleanUp();

Setup();
CleanReloadConfiguration();
}

private void _configService_SettingsChanged(object sender, EventArgs e)
{
LoadConfig();
CleanReloadConfiguration();
}

private void CleanReloadConfiguration()
{
LoadConfig();
CleanUp();

Setup();
}

Expand All @@ -84,18 +82,18 @@ private void LoadConfig()

private void Setup()
{
//_parser = new RubberduckParser(_factory);
//_parser = new RubberduckParser(_codePaneFactory);
_parser.ParseStarted += _parser_ParseStarted;
_parser.ParserError += _parser_ParserError;

_inspector = new Inspector(_parser, _configService);

_parserErrorsPresenter = new ParserErrorsPresenter(_vbe, _addIn);

_menu = new RubberduckMenu(_vbe, _addIn, _configService, _parser, _editor, _inspector, _factory);
_menu = new RubberduckMenu(_vbe, _addIn, _configService, _parser, _editor, _inspector, _navigateImplementations, _codePaneFactory);
_menu.Initialize();

_formContextMenu = new FormContextMenu(_vbe, _parser, _editor, _factory);
_formContextMenu = new FormContextMenu(_vbe, _parser, _editor, _codePaneFactory);
_formContextMenu.Initialize();

_codeInspectionsToolbar = new CodeInspectionsToolbar(_vbe, _inspector);
Expand Down
12 changes: 12 additions & 0 deletions RetailCoder.VBE/Navigations/INavigateImplementations.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
using Rubberduck.Parsing;
using Rubberduck.Parsing.Symbols;

namespace Rubberduck.Navigations
{
public interface INavigateImplementations
{
void Find();
void Find(Declaration target);
void Find(Declaration target, VBProjectParseResult parseResult);
}
}
161 changes: 161 additions & 0 deletions RetailCoder.VBE/Navigations/NavigateImplementations.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,161 @@
using System.Collections.Generic;
using System.Linq;
using System.Runtime.InteropServices;
using System.Windows.Forms;
using Microsoft.Vbe.Interop;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.UI;
using Rubberduck.UI.IdentifierReferences;
using Rubberduck.VBEditor;
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodePane;

namespace Rubberduck.Navigations
{
public class NavigateImplementations : INavigateImplementations
{
private readonly VBE _vbe;
private readonly AddIn _addIn;
private readonly IRubberduckParser _parser;
private readonly IRubberduckCodePaneFactory _codePaneFactory;
private readonly IRubberduckMessageBox _messageBox;

public NavigateImplementations(VBE vbe, AddIn addIn, IRubberduckParser parser, IRubberduckCodePaneFactory codePaneFactory, IRubberduckMessageBox messageBox)
{
_vbe = vbe;
_addIn = addIn;
_parser = parser;
_codePaneFactory = codePaneFactory;
_messageBox = messageBox;
}

public void Find()
{
var codePane = _codePaneFactory.Create(_vbe.ActiveCodePane);
var selection = new QualifiedSelection(new QualifiedModuleName(codePane.CodeModule.Parent), codePane.Selection);
var progress = new ParsingProgressPresenter();
var parseResult = progress.Parse(_parser, _vbe.ActiveVBProject);

var implementsStatement = parseResult.Declarations.FindInterfaces()
.SelectMany(i => i.References.Where(reference => reference.Context.Parent is VBAParser.ImplementsStmtContext))
.SingleOrDefault(r => r.QualifiedModuleName == selection.QualifiedName && r.Selection.Contains(selection.Selection));

if (implementsStatement != null)
{
Find(implementsStatement.Declaration, parseResult);
}

var member = parseResult.Declarations.FindInterfaceImplementationMembers()
.SingleOrDefault(m => m.Project == selection.QualifiedName.Project
&& m.ComponentName == selection.QualifiedName.ComponentName
&& m.Selection.Contains(selection.Selection)) ??
parseResult.Declarations.FindInterfaceMembers()
.SingleOrDefault(m => m.Project == selection.QualifiedName.Project
&& m.ComponentName == selection.QualifiedName.ComponentName
&& m.Selection.Contains(selection.Selection));

if (member == null)
{
return;
}

Find(member, parseResult);
}

public void Find(Declaration target)
{
var progress = new ParsingProgressPresenter();
var parseResult = progress.Parse(_parser, _vbe.ActiveVBProject);
Find(target, parseResult);
}

public void Find(Declaration target, VBProjectParseResult parseResult)
{
string name;
var implementations = (target.DeclarationType == DeclarationType.Class
? FindAllImplementationsOfClass(target, parseResult, out name)
: FindAllImplementationsOfMember(target, parseResult, out name)) ??
new List<Declaration>();

var declarations = implementations as IList<Declaration> ?? implementations.ToList();
var implementationsCount = declarations.Count();

if (implementationsCount == 1)
{
// if there's only 1 implementation, just jump to it:
ImplementationsListDockablePresenter.OnNavigateImplementation(_vbe, declarations.First());
}
else if (implementationsCount > 1)
{
// if there's more than one implementation, show the dockable navigation window:
try
{
ShowImplementationsToolwindow(declarations, name);
}
catch (COMException)
{
// the exception is related to the docked control host instance,
// trying again will work (I know, that's bad bad bad code)
ShowImplementationsToolwindow(declarations, name);
}
}
else
{
var message = string.Format(RubberduckUI.AllImplementations_NoneFound, name);
var caption = string.Format(RubberduckUI.AllImplementations_Caption, name);
_messageBox.Show(message, caption, MessageBoxButtons.OK, MessageBoxIcon.Information);
}
}

private IEnumerable<Declaration> FindAllImplementationsOfClass(Declaration target, VBProjectParseResult parseResult, out string name)
{
if (target.DeclarationType != DeclarationType.Class)
{
name = string.Empty;
return null;
}

var result = target.References
.Where(reference => reference.Context.Parent is VBAParser.ImplementsStmtContext)
.SelectMany(reference => parseResult.Declarations[reference.QualifiedModuleName.ComponentName])
.ToList();

name = target.ComponentName;
return result;
}

private IEnumerable<Declaration> FindAllImplementationsOfMember(Declaration target, VBProjectParseResult parseResult, out string name)
{
if (!target.DeclarationType.HasFlag(DeclarationType.Member))
{
name = string.Empty;
return null;
}

var isInterface = parseResult.Declarations.FindInterfaces()
.Select(i => i.QualifiedName.QualifiedModuleName.ToString())
.Contains(target.QualifiedName.QualifiedModuleName.ToString());

if (isInterface)
{
name = target.ComponentName + "." + target.IdentifierName;
return parseResult.Declarations.FindInterfaceImplementationMembers(target.IdentifierName)
.Where(item => item.IdentifierName == target.ComponentName + "_" + target.IdentifierName);
}

var member = parseResult.Declarations.FindInterfaceMember(target);
name = member.ComponentName + "." + member.IdentifierName;
return parseResult.Declarations.FindInterfaceImplementationMembers(member.IdentifierName)
.Where(item => item.IdentifierName == member.ComponentName + "_" + member.IdentifierName);
}

private void ShowImplementationsToolwindow(IEnumerable<Declaration> implementations, string name)
{
// throws a COMException if toolwindow was already closed
var window = new SimpleListControl(string.Format(RubberduckUI.AllImplementations_Caption, name));
var presenter = new ImplementationsListDockablePresenter(_vbe, _addIn, window, implementations, _codePaneFactory);
presenter.Show();
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -19,9 +19,9 @@ public class RemoveParametersModel
public Declaration TargetDeclaration { get; private set; }
public List<Parameter> Parameters { get; set; }

private readonly IMessageBox _messageBox;
private readonly IRubberduckMessageBox _messageBox;

public RemoveParametersModel(VBProjectParseResult parseResult, QualifiedSelection selection, IMessageBox messageBox)
public RemoveParametersModel(VBProjectParseResult parseResult, QualifiedSelection selection, IRubberduckMessageBox messageBox)
{
_parseResult = parseResult;
_declarations = parseResult.Declarations;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -12,9 +12,9 @@ public class RemoveParametersPresenter : IRemoveParametersPresenter
{
private readonly IRemoveParametersView _view;
private readonly RemoveParametersModel _model;
private readonly IMessageBox _messageBox;
private readonly IRubberduckMessageBox _messageBox;

public RemoveParametersPresenter(IRemoveParametersView view, RemoveParametersModel model, IMessageBox messageBox)
public RemoveParametersPresenter(IRemoveParametersView view, RemoveParametersModel model, IRubberduckMessageBox messageBox)
{
_view = view;
_model = model;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -9,10 +9,10 @@ public class RemoveParametersPresenterFactory : IRefactoringPresenterFactory<Rem
private readonly IActiveCodePaneEditor _editor;
private readonly IRemoveParametersView _view;
private readonly VBProjectParseResult _parseResult;
private readonly IMessageBox _messageBox;
private readonly IRubberduckMessageBox _messageBox;

public RemoveParametersPresenterFactory(IActiveCodePaneEditor editor, IRemoveParametersView view,
VBProjectParseResult parseResult, IMessageBox messageBox)
VBProjectParseResult parseResult, IRubberduckMessageBox messageBox)
{
_editor = editor;
_view = view;
Expand Down
4 changes: 2 additions & 2 deletions RetailCoder.VBE/Refactorings/Rename/RenameModel.cs
Original file line number Diff line number Diff line change
Expand Up @@ -31,9 +31,9 @@ public Declaration Target

public string NewName { get; set; }

private readonly IMessageBox _messageBox;
private readonly IRubberduckMessageBox _messageBox;

public RenameModel(VBE vbe, VBProjectParseResult parseResult, QualifiedSelection selection, IMessageBox messageBox)
public RenameModel(VBE vbe, VBProjectParseResult parseResult, QualifiedSelection selection, IRubberduckMessageBox messageBox)
{
_vbe = vbe;
_parseResult = parseResult;
Expand Down
4 changes: 2 additions & 2 deletions RetailCoder.VBE/Refactorings/Rename/RenamePresenterFactory.cs
Original file line number Diff line number Diff line change
Expand Up @@ -11,10 +11,10 @@ public class RenamePresenterFactory : IRefactoringPresenterFactory<RenamePresent
private readonly VBE _vbe;
private readonly IRenameView _view;
private readonly VBProjectParseResult _parseResult;
private readonly IMessageBox _messageBox;
private readonly IRubberduckMessageBox _messageBox;
private readonly IRubberduckCodePaneFactory _factory;

public RenamePresenterFactory(VBE vbe, IRenameView view, VBProjectParseResult parseResult, IMessageBox messageBox, IRubberduckCodePaneFactory factory)
public RenamePresenterFactory(VBE vbe, IRenameView view, VBProjectParseResult parseResult, IRubberduckMessageBox messageBox, IRubberduckCodePaneFactory factory)
{
_vbe = vbe;
_view = view;
Expand Down
4 changes: 2 additions & 2 deletions RetailCoder.VBE/Refactorings/Rename/RenameRefactoring.cs
Original file line number Diff line number Diff line change
Expand Up @@ -17,10 +17,10 @@ public class RenameRefactoring : IRefactoring
{
private readonly IRefactoringPresenterFactory<IRenamePresenter> _factory;
private readonly IActiveCodePaneEditor _editor;
private readonly IMessageBox _messageBox;
private readonly IRubberduckMessageBox _messageBox;
private RenameModel _model;

public RenameRefactoring(IRefactoringPresenterFactory<IRenamePresenter> factory, IActiveCodePaneEditor editor, IMessageBox messageBox)
public RenameRefactoring(IRefactoringPresenterFactory<IRenamePresenter> factory, IActiveCodePaneEditor editor, IRubberduckMessageBox messageBox)
{
_factory = factory;
_editor = editor;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -21,9 +21,9 @@ public class ReorderParametersModel
public Declaration TargetDeclaration { get; private set; }
public List<Parameter> Parameters { get; set; }

private readonly IMessageBox _messageBox;
private readonly IRubberduckMessageBox _messageBox;

public ReorderParametersModel(VBProjectParseResult parseResult, QualifiedSelection selection, IMessageBox messageBox)
public ReorderParametersModel(VBProjectParseResult parseResult, QualifiedSelection selection, IRubberduckMessageBox messageBox)
{
_parseResult = parseResult;
_declarations = parseResult.Declarations;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -12,9 +12,9 @@ public class ReorderParametersPresenter : IReorderParametersPresenter
{
private readonly IReorderParametersView _view;
private readonly ReorderParametersModel _model;
private readonly IMessageBox _messageBox;
private readonly IRubberduckMessageBox _messageBox;

public ReorderParametersPresenter(IReorderParametersView view, ReorderParametersModel model, IMessageBox messageBox)
public ReorderParametersPresenter(IReorderParametersView view, ReorderParametersModel model, IRubberduckMessageBox messageBox)
{
_view = view;
_model = model;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -9,10 +9,10 @@ public class ReorderParametersPresenterFactory : IRefactoringPresenterFactory<IR
private readonly IActiveCodePaneEditor _editor;
private readonly IReorderParametersView _view;
private readonly VBProjectParseResult _parseResult;
private readonly IMessageBox _messageBox;
private readonly IRubberduckMessageBox _messageBox;

public ReorderParametersPresenterFactory(IActiveCodePaneEditor editor, IReorderParametersView view,
VBProjectParseResult parseResult, IMessageBox messageBox)
VBProjectParseResult parseResult, IRubberduckMessageBox messageBox)
{
_editor = editor;
_view = view;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -18,9 +18,9 @@ public class ReorderParametersRefactoring : IRefactoring
private readonly IRefactoringPresenterFactory<IReorderParametersPresenter> _factory;
private readonly IActiveCodePaneEditor _editor;
private ReorderParametersModel _model;
private readonly IMessageBox _messageBox;
private readonly IRubberduckMessageBox _messageBox;

public ReorderParametersRefactoring(IRefactoringPresenterFactory<IReorderParametersPresenter> factory, IActiveCodePaneEditor editor, IMessageBox messageBox)
public ReorderParametersRefactoring(IRefactoringPresenterFactory<IReorderParametersPresenter> factory, IActiveCodePaneEditor editor, IRubberduckMessageBox messageBox)
{
_factory = factory;
_editor = editor;
Expand Down
Loading