Skip to content

Commit

Permalink
Merge branch 'next' into feature/Com_Reference_Explorer
Browse files Browse the repository at this point in the history
  • Loading branch information
rossknudsen committed Jul 8, 2016
2 parents 50b0618 + 8fc93ec commit ae1b3d6
Show file tree
Hide file tree
Showing 26 changed files with 216 additions and 392 deletions.
2 changes: 1 addition & 1 deletion RetailCoder.VBE/API/ParserState.cs
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ public void Initialize(VBE vbe)

Func<IVBAPreprocessor> preprocessorFactory = () => new VBAPreprocessor(double.Parse(vbe.Version, CultureInfo.InvariantCulture));
_attributeParser = new AttributeParser(new ModuleExporter(), preprocessorFactory);
_parser = new RubberduckParser(vbe, _state, _attributeParser, preprocessorFactory,
_parser = new RubberduckParser(_state, _attributeParser, preprocessorFactory,
new List<ICustomDeclarationLoader> { new DebugDeclarations(_state), new FormEventDeclarations(_state) });
}

Expand Down
27 changes: 14 additions & 13 deletions RetailCoder.VBE/Common/RubberduckHooks.cs
Original file line number Diff line number Diff line change
Expand Up @@ -173,12 +173,6 @@ public void Detach()

private void hook_MessageReceived(object sender, HookEventArgs e)
{
var active = User32.GetForegroundWindow();
if (active != _mainWindowHandle)
{
return;
}

var hotkey = sender as IHotkey;
if (hotkey != null)
{
Expand Down Expand Up @@ -207,6 +201,16 @@ private IntPtr WindowProc(IntPtr hWnd, uint uMsg, IntPtr wParam, IntPtr lParam)
case WM.SETFOCUS:
Attach();
break;
case WM.RUBBERDUCK_CHILD_FOCUS:
if (lParam == IntPtr.Zero)
{
Detach();
}
else
{
Attach();
}
return IntPtr.Zero;
case WM.NCACTIVATE:
if (wParam == IntPtr.Zero)
{
Expand Down Expand Up @@ -235,14 +239,11 @@ private bool HandleHotkeyMessage(IntPtr wParam)
var processed = false;
try
{
if (User32.IsVbeWindowActive(_mainWindowHandle))
var hook = Hooks.OfType<Hotkey>().SingleOrDefault(k => k.HotkeyInfo.HookId == wParam);
if (hook != null)
{
var hook = Hooks.OfType<Hotkey>().SingleOrDefault(k => k.HotkeyInfo.HookId == wParam);
if (hook != null)
{
hook.OnMessageReceived();
processed = true;
}
hook.OnMessageReceived();
processed = true;
}
}
catch (Exception exception)
Expand Down
3 changes: 3 additions & 0 deletions RetailCoder.VBE/Common/WinAPI/User32.cs
Original file line number Diff line number Diff line change
Expand Up @@ -180,6 +180,9 @@ public static class User32
[DllImport("user32.dll", SetLastError = true)]
internal static extern bool UnregisterDeviceNotification(IntPtr handle);

[DllImport("user32.dll", CharSet = CharSet.Auto)]
internal static extern IntPtr SendMessage(IntPtr hWnd, WM msg, IntPtr wParam, IntPtr lParam);

/// <summary>
/// A helper function that returns <c>true</c> when the specified handle is that of the foreground window.
/// </summary>
Expand Down
5 changes: 5 additions & 0 deletions RetailCoder.VBE/Common/WinAPI/WM.cs
Original file line number Diff line number Diff line change
Expand Up @@ -922,6 +922,11 @@ public enum WM : uint
/// </summary>
SYSTIMER = 0x118,

/// <summary>
/// Private message to signal focus set/lost for a DockableWindowHost. Set wParam to the DockableWindowHost hWnd, lParam to zero for lost focus, non-zero for gained focus.
/// </summary>
RUBBERDUCK_CHILD_FOCUS = USER + 0x0F00,

/// <summary>
/// The accessibility state has changed.
/// </summary>
Expand Down
2 changes: 1 addition & 1 deletion RetailCoder.VBE/Inspections/InspectionResultBase.cs
Original file line number Diff line number Diff line change
Expand Up @@ -121,7 +121,7 @@ public int CompareTo(object obj)
public object[] ToArray()
{
var module = QualifiedSelection.QualifiedName;
return new object[] { Inspection.Severity.ToString(), module.ProjectTitle, module.ComponentName, Description, QualifiedSelection.Selection.StartLine, QualifiedSelection.Selection.StartColumn };
return new object[] { Inspection.Severity.ToString(), module.ProjectName, module.ComponentName, Description, QualifiedSelection.Selection.StartLine, QualifiedSelection.Selection.StartColumn };
}

public string ToCsvString()
Expand Down
44 changes: 15 additions & 29 deletions RetailCoder.VBE/Navigation/CodeExplorer/CodeExplorerViewModel.cs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@
using System.Collections.Generic;
using System.Collections.ObjectModel;
using System.Linq;
using System.Windows.Input;
using Microsoft.Vbe.Interop;
using NLog;
using Rubberduck.Navigation.Folders;
Expand Down Expand Up @@ -33,8 +32,7 @@ public CodeExplorerViewModel(FolderHelper folderHelper, RubberduckParserState st

_refreshCommand = new DelegateCommand(LogManager.GetCurrentClassLogger(), param => _state.OnParseRequested(this),
param => !IsBusy && _state.IsDirty());

_refreshComponentCommand = commands.OfType<CodeExplorer_RefreshComponentCommand>().FirstOrDefault();

_navigateCommand = commands.OfType<CodeExplorer_NavigateCommand>().FirstOrDefault();

_addTestModuleCommand = commands.OfType<CodeExplorer_AddTestModuleCommand>().FirstOrDefault();
Expand Down Expand Up @@ -87,17 +85,6 @@ public CodeExplorerItemViewModel SelectedItem
_selectedItem = value;
OnPropertyChanged();

if (_selectedItem is CodeExplorerProjectViewModel)
{
var vbe = _selectedItem.GetSelectedDeclaration().Project.VBE;
var project = vbe.VBProjects.Cast<VBProject>().FirstOrDefault(f => f.HelpFile == _selectedItem.GetSelectedDeclaration().Project.HelpFile);

if (project != null)
{
vbe.ActiveVBProject = project;
}
}

// ReSharper disable ExplicitCallerInfoArgument
OnPropertyChanged("CanExecuteIndenterCommand");
OnPropertyChanged("CanExecuteRenameCommand");
Expand Down Expand Up @@ -189,25 +176,27 @@ public string PanelTitle
return string.Empty;
}

if (SelectedItem is CodeExplorerProjectViewModel)
if (!(SelectedItem is ICodeExplorerDeclarationViewModel))
{
var node = (CodeExplorerProjectViewModel)SelectedItem;
return node.Declaration.IdentifierName + string.Format(" - ({0})", node.Declaration.DeclarationType);
return SelectedItem.Name;
}

if (SelectedItem is CodeExplorerComponentViewModel)
{
var node = (CodeExplorerComponentViewModel)SelectedItem;
return node.Declaration.IdentifierName + string.Format(" - ({0})", node.Declaration.DeclarationType);
}
var declaration = SelectedItem.GetSelectedDeclaration();

var nameWithDeclarationType = declaration.IdentifierName +
string.Format(" - ({0})", RubberduckUI.ResourceManager.GetString(
"DeclarationType_" + declaration.DeclarationType, UI.Settings.Settings.Culture));

if (SelectedItem is CodeExplorerMemberViewModel)
if (string.IsNullOrEmpty(declaration.AsTypeName))
{
var node = (CodeExplorerMemberViewModel)SelectedItem;
return node.Declaration.IdentifierName + string.Format(" - ({0})", node.Declaration.DeclarationType);
return nameWithDeclarationType;
}

return SelectedItem.Name;
var typeName = declaration.HasTypeHint
? Declaration.TypeHintToTypeName[declaration.TypeHint]
: declaration.AsTypeName;

return nameWithDeclarationType + ": " + typeName;
}
}

Expand Down Expand Up @@ -423,9 +412,6 @@ private void SetErrorState(CodeExplorerItemViewModel itemNode, VBComponent compo
private readonly CommandBase _refreshCommand;
public CommandBase RefreshCommand { get { return _refreshCommand; } }

private readonly CommandBase _refreshComponentCommand;
public CommandBase RefreshComponentCommand { get { return _refreshComponentCommand; } }

private readonly CommandBase _navigateCommand;
public CommandBase NavigateCommand { get { return _navigateCommand; } }

Expand Down
3 changes: 1 addition & 2 deletions RetailCoder.VBE/Rubberduck.csproj
Original file line number Diff line number Diff line change
Expand Up @@ -423,7 +423,6 @@
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_AddUserFormCommand.cs" />
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_CopyResultsCommand.cs" />
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_OpenProjectPropertiesCommand.cs" />
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_RefreshComponentCommand.cs" />
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_RenameCommand.cs" />
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_FindAllReferencesCommand.cs" />
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_FindAllImplementationsCommand.cs" />
Expand Down Expand Up @@ -977,7 +976,7 @@
<Compile Include="UnitTesting\AssertClass.cs" />
<Compile Include="UnitTesting\AssertCompletedEventArgs.cs" />
<Compile Include="UnitTesting\AssertHandler.cs" />
<Compile Include="UnitTesting\UnitTestHelpers.cs" />
<Compile Include="UnitTesting\UnitTestUtils.cs" />
<Compile Include="UnitTesting\IAssert.cs" />
<Compile Include="UnitTesting\ITestEngine.cs" />
<Compile Include="UnitTesting\ITestRunner.cs" />
Expand Down
14 changes: 7 additions & 7 deletions RetailCoder.VBE/UI/CodeExplorer/CodeExplorerControl.xaml
Original file line number Diff line number Diff line change
Expand Up @@ -357,9 +357,8 @@
<Setter Property="ContextMenu">
<Setter.Value>
<ContextMenu DataContext="{Binding DataContext, Source={x:Reference CodeExplorer}}">
<MenuItem Header="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=CodeExplorer_RefreshComponent}"
Command="{Binding RefreshComponentCommand}"
CommandParameter="{Binding SelectedItem}">
<MenuItem Header="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=Refresh}"
Command="{Binding RefreshCommand}">
<MenuItem.Icon>
<Image Source="{StaticResource RefreshImage}" />
</MenuItem.Icon>
Expand All @@ -374,7 +373,8 @@
CommandParameter="{Binding SelectedItem}" />
<Separator />
<MenuItem Header="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=CodeExplorer_OpenProjectProperties}"
Command="{Binding OpenProjectPropertiesCommand}" />
Command="{Binding OpenProjectPropertiesCommand}"
CommandParameter="{Binding SelectedItem}" />
<Separator />
<MenuItem Header="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=Add}">
<MenuItem Header="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=CodeExplorer_AddTestModuleText}"
Expand Down Expand Up @@ -740,8 +740,8 @@

<Border Grid.Row="3" BorderThickness="0,1,0,0" BorderBrush="DimGray">

<ScrollViewer Background="WhiteSmoke" VerticalScrollBarVisibility="Auto" HorizontalScrollBarVisibility="Auto">
<StackPanel Orientation="Vertical" MinHeight="48" Background="WhiteSmoke">
<ScrollViewer Background="WhiteSmoke" VerticalScrollBarVisibility="Auto">
<WrapPanel Orientation="Vertical" MinHeight="48" Background="WhiteSmoke">

<Grid Margin="4" HorizontalAlignment="Stretch">
<Grid.ColumnDefinitions>
Expand Down Expand Up @@ -776,7 +776,7 @@
CommandParameter="{Binding SelectedItem}"
Content="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=CodeExplorer_FindAllReferencesText}" />
</WrapPanel>
</StackPanel>
</WrapPanel>
</ScrollViewer>
</Border>
</Grid>
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
using System.Runtime.InteropServices;
using Microsoft.Vbe.Interop;
using NLog;
using Rubberduck.Navigation.CodeExplorer;
using Rubberduck.UI.Command;

namespace Rubberduck.UI.CodeExplorer.Commands
Expand All @@ -13,10 +15,36 @@ public CodeExplorer_OpenProjectPropertiesCommand(VBE vbe) : base(LogManager.GetC
_vbe = vbe;
}

protected override bool CanExecuteImpl(object parameter)
{
return parameter != null || _vbe.VBProjects.Count == 1;
}

protected override void ExecuteImpl(object parameter)
{
const int openProjectPropertiesId = 2578;

if (_vbe.VBProjects.Count == 1)
{
_vbe.CommandBars.FindControl(Id: openProjectPropertiesId).Execute();
return;
}

var node = parameter as CodeExplorerItemViewModel;
while (!(node is ICodeExplorerDeclarationViewModel))
{
node = node.Parent; // the project node is an ICodeExplorerDeclarationViewModel--no worries here
}

try
{
_vbe.ActiveVBProject = node.GetSelectedDeclaration().Project;
}
catch (COMException)
{
return; // the project was probably removed from the VBE, but not from the CE
}

_vbe.CommandBars.FindControl(Id: openProjectPropertiesId).Execute();
}
}
Expand Down

This file was deleted.

13 changes: 11 additions & 2 deletions RetailCoder.VBE/UI/Command/AddTestMethodCommand.cs
Original file line number Diff line number Diff line change
Expand Up @@ -34,8 +34,17 @@ protected override bool CanExecuteImpl(object parameter)
d.DeclarationType == DeclarationType.ProceduralModule &&
d.Annotations.Any(a => a.AnnotationType == AnnotationType.TestModule));

// the code modules consistently match correctly, but the components don't
return testModules.Any(a => a.QualifiedName.QualifiedModuleName.Component.CodeModule == _vbe.SelectedVBComponent.CodeModule);
try
{
// the code modules consistently match correctly, but the components don't
return testModules.Any(a =>
a.QualifiedName.QualifiedModuleName.Component.CodeModule ==
_vbe.SelectedVBComponent.CodeModule);
}
catch (COMException)
{
return false;
}
}

protected override void ExecuteImpl(object parameter)
Expand Down
13 changes: 11 additions & 2 deletions RetailCoder.VBE/UI/Command/AddTestMethodExpectedErrorCommand.cs
Original file line number Diff line number Diff line change
Expand Up @@ -34,8 +34,17 @@ protected override bool CanExecuteImpl(object parameter)
d.DeclarationType == DeclarationType.ProceduralModule &&
d.Annotations.Any(a => a.AnnotationType == AnnotationType.TestModule));

// the code modules consistently match correctly, but the components don't
return testModules.Any(a => a.QualifiedName.QualifiedModuleName.Component.CodeModule == _vbe.SelectedVBComponent.CodeModule);
try
{
// the code modules consistently match correctly, but the components don't
return testModules.Any(a =>
a.QualifiedName.QualifiedModuleName.Component.CodeModule ==
_vbe.SelectedVBComponent.CodeModule);
}
catch (COMException)
{
return false;
}
}

protected override void ExecuteImpl(object parameter)
Expand Down
2 changes: 1 addition & 1 deletion RetailCoder.VBE/UI/DockableToolwindowPresenter.cs
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ private Window CreateToolWindow(IDockableUserControl control)

toolWindow.Visible = false; //hide it again

userControlHost.AddUserControl(control as UserControl);
userControlHost.AddUserControl(control as UserControl, new IntPtr(_vbe.MainWindow.HWnd));
return toolWindow;
}

Expand Down

0 comments on commit ae1b3d6

Please sign in to comment.