Skip to content

Commit

Permalink
Merge pull request #2287 from retailcoder/next
Browse files Browse the repository at this point in the history
Implemented SafeComWrappers
  • Loading branch information
retailcoder committed Oct 5, 2016
2 parents 88f6127 + b2ff5b8 commit 710f6f4
Show file tree
Hide file tree
Showing 329 changed files with 8,962 additions and 5,420 deletions.
3 changes: 2 additions & 1 deletion RetailCoder.VBE/API/ParserState.cs
Original file line number Diff line number Diff line change
Expand Up @@ -3,13 +3,14 @@
using System.ComponentModel;
using System.Linq;
using System.Runtime.InteropServices;
using Microsoft.Vbe.Interop;
using Rubberduck.Common;
using Rubberduck.Parsing.VBA;
using Rubberduck.UI.Command.MenuItems;
using Rubberduck.Parsing.Preprocessing;
using System.Globalization;
using Rubberduck.Parsing.Symbols;
using Rubberduck.VBEditor.DisposableWrappers;
using Rubberduck.VBEditor.DisposableWrappers.VBA;

namespace Rubberduck.API
{
Expand Down
35 changes: 21 additions & 14 deletions RetailCoder.VBE/App.cs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
using System.IO;
using Infralution.Localization.Wpf;
using Microsoft.Vbe.Interop;
using NLog;
using Rubberduck.Common;
using Rubberduck.Parsing;
Expand All @@ -12,6 +11,7 @@
using System;
using System.Globalization;
using System.Windows.Forms;
using Rubberduck.VBEditor.DisposableWrappers.VBA;

namespace Rubberduck
{
Expand Down Expand Up @@ -79,17 +79,24 @@ private void _hooks_MessageReceived(object sender, HookEventArgs e)

private void RefreshSelection()
{
var selectedDeclaration = _parser.State.FindSelectedDeclaration(_vbe.ActiveCodePane);
_stateBar.SetSelectionText(selectedDeclaration);

var currentStatus = _parser.State.Status;
if (ShouldEvaluateCanExecute(selectedDeclaration, currentStatus))
var pane = _vbe.ActiveCodePane;
{
_appMenus.EvaluateCanExecute(_parser.State);
}
Declaration selectedDeclaration = null;
if (!pane.IsWrappingNullReference)
{
selectedDeclaration = _parser.State.FindSelectedDeclaration(pane);
_stateBar.SetSelectionText(selectedDeclaration);
}

var currentStatus = _parser.State.Status;
if (ShouldEvaluateCanExecute(selectedDeclaration, currentStatus))
{
_appMenus.EvaluateCanExecute(_parser.State);
}

_lastStatus = currentStatus;
_lastSelectedDeclaration = selectedDeclaration;
_lastStatus = currentStatus;
_lastSelectedDeclaration = selectedDeclaration;
}
}

private bool ShouldEvaluateCanExecute(Declaration selectedDeclaration, ParserState currentStatus)
Expand Down Expand Up @@ -142,10 +149,10 @@ public void Startup()
_appMenus.Localize();
UpdateLoggingLevel();

if (_vbe.VBProjects.Count != 0)
{
_parser.State.OnParseRequested(this);
}
//if (_vbe.VBProjects.Count != 0)
//{
// _parser.State.OnParseRequested(this);
//}
}

public void Shutdown()
Expand Down
15 changes: 10 additions & 5 deletions RetailCoder.VBE/AutoSave/AutoSave.cs
Original file line number Diff line number Diff line change
@@ -1,9 +1,10 @@
using System;
using System.IO;
using System.Linq;
using System.Runtime.InteropServices;
using System.Timers;
using Microsoft.Vbe.Interop;
using Rubberduck.Settings;
using Rubberduck.VBEditor.DisposableWrappers.VBA;

namespace Rubberduck.AutoSave
{
Expand Down Expand Up @@ -37,26 +38,30 @@ public void ConfigServiceSettingsChanged(object sender, EventArgs e)

private void _timer_Elapsed(object sender, ElapsedEventArgs e)
{
if (_vbe.VBProjects.OfType<VBProject>().Any(p => !p.Saved))
var projects = _vbe.VBProjects;
if (projects.Any(p => !p.Saved))
{
try
{
var projects = _vbe.VBProjects.OfType<VBProject>().Select(p => p.FileName).ToList();
var foo = projects.Select(p => p.FileName).ToList();
}
catch (IOException)
{
// note: VBProject.FileName getter throws IOException if unsaved
return;
}

_vbe.CommandBars.FindControl(Id: VbeSaveCommandId).Execute();
var commandBars = _vbe.CommandBars;
var control = commandBars.FindControl(VbeSaveCommandId);
control.Execute();
Marshal.ReleaseComObject(control);
Marshal.ReleaseComObject(commandBars);
}
}

public void Dispose()
{
Dispose(true);
GC.SuppressFinalize(this);
}

private void Dispose(bool disposing)
Expand Down
6 changes: 4 additions & 2 deletions RetailCoder.VBE/Common/DeclarationExtensions.cs
Original file line number Diff line number Diff line change
Expand Up @@ -4,14 +4,16 @@
using System.Diagnostics.CodeAnalysis;
using System.Linq;
using System.Windows.Media.Imaging;
using Microsoft.Vbe.Interop;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Properties;
using Rubberduck.UI;
using Rubberduck.VBEditor;
using Rubberduck.VBEditor.DisposableWrappers;
using Rubberduck.VBEditor.DisposableWrappers.VBA;

// ReSharper disable LocalizableElement

namespace Rubberduck.Common
Expand Down Expand Up @@ -353,7 +355,7 @@ public static IEnumerable<Declaration> FindFormEventHandlers(this RubberduckPars

var forms = items.Where(item => item.DeclarationType == DeclarationType.ClassModule
&& item.QualifiedName.QualifiedModuleName.Component != null
&& item.QualifiedName.QualifiedModuleName.Component.Type == vbext_ComponentType.vbext_ct_MSForm)
&& item.QualifiedName.QualifiedModuleName.Component.Type == ComponentType.UserForm)
.ToList();

var result = new List<Declaration>();
Expand Down
3 changes: 2 additions & 1 deletion RetailCoder.VBE/Common/ModuleExporter.cs
Original file line number Diff line number Diff line change
@@ -1,8 +1,9 @@
using System.IO;
using System.Reflection;
using Microsoft.Vbe.Interop;
using Rubberduck.VBEditor.Extensions;
using Rubberduck.Parsing.VBA;
using Rubberduck.VBEditor.DisposableWrappers;
using Rubberduck.VBEditor.DisposableWrappers.VBA;

namespace Rubberduck.Common
{
Expand Down
9 changes: 7 additions & 2 deletions RetailCoder.VBE/Common/RubberduckHooks.cs
Original file line number Diff line number Diff line change
Expand Up @@ -5,12 +5,13 @@
using System.Linq;
using System.Runtime.InteropServices;
using System.Windows.Forms;
using Microsoft.Vbe.Interop;
using Rubberduck.Common.Hotkeys;
using Rubberduck.Common.WinAPI;
using Rubberduck.Settings;
using Rubberduck.UI.Command;
using NLog;
using Rubberduck.VBEditor.DisposableWrappers;
using Rubberduck.VBEditor.DisposableWrappers.VBA;

namespace Rubberduck.Common
{
Expand All @@ -30,7 +31,11 @@ public class RubberduckHooks : IRubberduckHooks

public RubberduckHooks(VBE vbe, IGeneralConfigService config, IEnumerable<CommandBase> commands)
{
_mainWindowHandle = (IntPtr)vbe.MainWindow.HWnd;
var mainWindow = vbe.MainWindow;
{
_mainWindowHandle = (IntPtr)mainWindow.HWnd;
}

_oldWndProc = WindowProc;
_newWndProc = WindowProc;
_oldWndPointer = User32.SetWindowLong(_mainWindowHandle, (int)WindowLongFlags.GWL_WNDPROC, _newWndProc);
Expand Down
117 changes: 93 additions & 24 deletions RetailCoder.VBE/Extension.cs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
using Rubberduck.UI;
using System;
using System.ComponentModel;
using System.Diagnostics.CodeAnalysis;
using System.Globalization;
using System.IO;
using System.Reflection;
Expand All @@ -19,6 +20,9 @@

namespace Rubberduck
{
/// <remarks>
/// Special thanks to Carlos Quintero (MZ-Tools) for providing the general structure here.
/// </remarks>
[ComVisible(true)]
[Guid(ClassId)]
[ProgId(ProgId)]
Expand All @@ -29,22 +33,100 @@ public class _Extension : IDTExtensibility2
private const string ClassId = "8D052AD8-BBD2-4C59-8DEC-F697CA1F8A66";
private const string ProgId = "Rubberduck.Extension";

private VBEditor.DisposableWrappers.VBA.VBE _ide;
private VBEditor.DisposableWrappers.VBA.AddIn _addin;
private bool _isInitialized;
private bool _isBeginShutdownExecuted;

private IKernel _kernel;
private App _app;
private readonly Logger _logger = LogManager.GetCurrentClassLogger();

public void OnAddInsUpdate(ref Array custom)
public void OnAddInsUpdate(ref Array custom) { }

[SuppressMessage("ReSharper", "InconsistentNaming")]
public void OnConnection(object Application, ext_ConnectMode ConnectMode, object AddInInst, ref Array custom)
{
try
{
_ide = new VBEditor.DisposableWrappers.VBA.VBE((VBE)Application);
_addin = new VBEditor.DisposableWrappers.VBA.AddIn((AddIn)AddInInst);
_addin.Object = this;

switch (ConnectMode)
{
case ext_ConnectMode.ext_cm_Startup:
// normal execution path - don't initialize just yet, wait for OnStartupComplete to be called by the host.
break;
case ext_ConnectMode.ext_cm_AfterStartup:
InitializeAddIn();
break;
}
}
catch (Exception e)
{
Console.WriteLine(e);
}
}

Assembly LoadFromSameFolder(object sender, ResolveEventArgs args)
{
var folderPath = Path.GetDirectoryName(Assembly.GetExecutingAssembly().Location);
var assemblyPath = Path.Combine(folderPath, new AssemblyName(args.Name).Name + ".dll");
if (!File.Exists(assemblyPath))
{
return null;
}

var assembly = Assembly.LoadFile(assemblyPath);
return assembly;
}

public void OnStartupComplete(ref Array custom)
{
InitializeAddIn();
}

public void OnBeginShutdown(ref Array custom)
{
_isBeginShutdownExecuted = true;
ShutdownAddIn();
}

// ReSharper disable InconsistentNaming
public void OnConnection(object Application, ext_ConnectMode ConnectMode, object AddInInst, ref Array custom)
public void OnDisconnection(ext_DisconnectMode RemoveMode, ref Array custom)
{
_kernel = new StandardKernel(new NinjectSettings{LoadExtensions = true}, new FuncModule(), new DynamicProxyModule());
switch (RemoveMode)
{
case ext_DisconnectMode.ext_dm_UserClosed:
ShutdownAddIn();
break;

case ext_DisconnectMode.ext_dm_HostShutdown:
if (_isBeginShutdownExecuted)
{
// this is the normal case: nothing to do here, we already ran ShutdownAddIn.
}
else
{
// some hosts do not call OnBeginShutdown: this mitigates it.
ShutdownAddIn();
}
break;
}
}

private void InitializeAddIn()
{
if (_isInitialized)
{
// The add-in is already initialized. See:
// The strange case of the add-in initialized twice
// http://msmvps.com/blogs/carlosq/archive/2013/02/14/the-strange-case-of-the-add-in-initialized-twice.aspx
return;
}

_kernel = new StandardKernel(new NinjectSettings { LoadExtensions = true }, new FuncModule(), new DynamicProxyModule());

try
{
Expand All @@ -53,8 +135,7 @@ public void OnConnection(object Application, ext_ConnectMode ConnectMode, object

var config = new XmlPersistanceService<GeneralSettings>
{
FilePath = Path.Combine(Environment.GetFolderPath(Environment.SpecialFolder.ApplicationData), "Rubberduck",
"rubberduck.config")
FilePath = Path.Combine(Environment.GetFolderPath(Environment.SpecialFolder.ApplicationData), "Rubberduck", "rubberduck.config")
};

var settings = config.Load(null);
Expand All @@ -68,9 +149,11 @@ public void OnConnection(object Application, ext_ConnectMode ConnectMode, object
catch (CultureNotFoundException) { }
}

_kernel.Load(new RubberduckModule((VBE)Application, (AddIn)AddInInst));
_kernel.Load(new RubberduckModule(_ide, _addin));

_app = _kernel.Get<App>();
_app.Startup();
_isInitialized = true;
}
catch (Exception exception)
{
Expand All @@ -79,24 +162,7 @@ public void OnConnection(object Application, ext_ConnectMode ConnectMode, object
}
}

Assembly LoadFromSameFolder(object sender, ResolveEventArgs args)
{
var folderPath = Path.GetDirectoryName(Assembly.GetExecutingAssembly().Location);
var assemblyPath = Path.Combine(folderPath, new AssemblyName(args.Name).Name + ".dll");
if (!File.Exists(assemblyPath))
{
return null;
}

var assembly = Assembly.LoadFile(assemblyPath);
return assembly;
}

public void OnStartupComplete(ref Array custom)
{
}

public void OnDisconnection(ext_DisconnectMode RemoveMode, ref Array custom)
private void ShutdownAddIn()
{
if (_app != null)
{
Expand All @@ -109,6 +175,9 @@ public void OnDisconnection(ext_DisconnectMode RemoveMode, ref Array custom)
_kernel.Dispose();
_kernel = null;
}

_ide.Release();
_isInitialized = false;
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -48,10 +48,11 @@ public override void Fix()
var selection = Selection.Selection;

var module = Selection.QualifiedName.Component.CodeModule;
var lines = module.get_Lines(selection.StartLine, selection.LineCount);

var result = lines.Replace(parameter, newContent);
module.ReplaceLine(selection.StartLine, result);
{
var lines = module.GetLines(selection.StartLine, selection.LineCount);
var result = lines.Replace(parameter, newContent);
module.ReplaceLine(selection.StartLine, result);
}
}
}
}

0 comments on commit 710f6f4

Please sign in to comment.