Skip to content

Commit

Permalink
Merge pull request #4092 from MDoerner/FixRenameOfUdt
Browse files Browse the repository at this point in the history
Fix rename of UDTs
  • Loading branch information
retailcoder committed Jun 17, 2018
2 parents c5bb40f + 6ac12aa commit 27f33e3
Show file tree
Hide file tree
Showing 7 changed files with 293 additions and 49 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -89,8 +89,7 @@ public override bool VisitModuleDeclarationsElement(VBAParser.ModuleDeclarations
return context.variableStmt() == null
&& context.constStmt() == null
&& context.enumerationStmt() == null
&& context.privateTypeDeclaration() == null
&& context.publicTypeDeclaration() == null
&& context.udtDeclaration() == null
&& context.eventStmt() == null
&& context.implementsStmt() == null
&& context.declareStmt() == null;
Expand Down
7 changes: 2 additions & 5 deletions Rubberduck.Parsing/Grammar/VBAParser.g4
Original file line number Diff line number Diff line change
Expand Up @@ -90,8 +90,7 @@ moduleDeclarationsElement :
| implementsStmt
| variableStmt
| moduleOption
| publicTypeDeclaration
| privateTypeDeclaration)
| udtDeclaration)
;

moduleBody :
Expand Down Expand Up @@ -518,10 +517,8 @@ subStmt :
subroutineName : identifier;

// 5.2.3.3 User Defined Type Declarations
publicTypeDeclaration : ((GLOBAL | PUBLIC) whiteSpace)? udtDeclaration;
privateTypeDeclaration : PRIVATE whiteSpace udtDeclaration;
// member list includes trailing endOfStatement
udtDeclaration : TYPE whiteSpace untypedIdentifier endOfStatement udtMemberList END_TYPE;
udtDeclaration : (visibility whiteSpace)? TYPE whiteSpace untypedIdentifier endOfStatement udtMemberList END_TYPE;
udtMemberList : (udtMember endOfStatement)+;
udtMember : reservedNameMemberDeclaration | untypedNameMemberDeclaration;
untypedNameMemberDeclaration : untypedIdentifier whiteSpace? optionalArrayClause;
Expand Down
23 changes: 7 additions & 16 deletions Rubberduck.Parsing/Symbols/DeclarationSymbolsListener.cs
Original file line number Diff line number Diff line change
Expand Up @@ -751,30 +751,21 @@ public override void EnterConstSubStmt(VBAParser.ConstSubStmtContext context)
AddDeclaration(declaration);
}

public override void EnterPublicTypeDeclaration(VBAParser.PublicTypeDeclarationContext context)
public override void EnterUdtDeclaration(VBAParser.UdtDeclarationContext context)
{
AddUdtDeclaration(context.udtDeclaration(), Accessibility.Public, context);
AddUdtDeclaration(context);
}

public override void ExitPublicTypeDeclaration(VBAParser.PublicTypeDeclarationContext context)
public override void ExitUdtDeclaration(VBAParser.UdtDeclarationContext context)
{
_parentDeclaration = _moduleDeclaration;
}

public override void EnterPrivateTypeDeclaration(VBAParser.PrivateTypeDeclarationContext context)
private void AddUdtDeclaration(VBAParser.UdtDeclarationContext context)
{
AddUdtDeclaration(context.udtDeclaration(), Accessibility.Private, context);
}

public override void ExitPrivateTypeDeclaration(VBAParser.PrivateTypeDeclarationContext context)
{
_parentDeclaration = _moduleDeclaration;
}

private void AddUdtDeclaration(VBAParser.UdtDeclarationContext udtDeclaration, Accessibility accessibility, ParserRuleContext context)
{
var identifier = Identifier.GetName(udtDeclaration.untypedIdentifier());
var identifierSelection = Identifier.GetNameSelection(udtDeclaration.untypedIdentifier());
var identifier = Identifier.GetName(context.untypedIdentifier());
var identifierSelection = Identifier.GetNameSelection(context.untypedIdentifier());
var accessibility = context.visibility()?.PRIVATE() != null ? Accessibility.Private : Accessibility.Public;
var declaration = CreateDeclaration(
identifier,
null,
Expand Down
16 changes: 3 additions & 13 deletions Rubberduck.Parsing/Symbols/IdentifierReferenceListener.cs
Original file line number Diff line number Diff line change
Expand Up @@ -86,22 +86,12 @@ public override void ExitEnumerationStmt(VBAParser.EnumerationStmtContext contex
SetCurrentScope();
}

public override void EnterPublicTypeDeclaration(VBAParser.PublicTypeDeclarationContext context)
public override void EnterUdtDeclaration(VBAParser.UdtDeclarationContext context)
{
SetCurrentScope(Identifier.GetName(context.udtDeclaration().untypedIdentifier()), DeclarationType.UserDefinedType);
SetCurrentScope(Identifier.GetName(context.untypedIdentifier()), DeclarationType.UserDefinedType);
}

public override void ExitPublicTypeDeclaration(VBAParser.PublicTypeDeclarationContext context)
{
SetCurrentScope();
}

public override void EnterPrivateTypeDeclaration(VBAParser.PrivateTypeDeclarationContext context)
{
SetCurrentScope(Identifier.GetName(context.udtDeclaration().untypedIdentifier()), DeclarationType.UserDefinedType);
}

public override void ExitPrivateTypeDeclaration(VBAParser.PrivateTypeDeclarationContext context)
public override void ExitUdtDeclaration(VBAParser.UdtDeclarationContext context)
{
SetCurrentScope();
}
Expand Down
2 changes: 1 addition & 1 deletion Rubberduck.Parsing/VBA/COMReferenceSynchronizerBase.cs
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,7 @@ public void SyncComReferences(IReadOnlyList<IVBProject> projects, CancellationTo
}
}

private IEnumerable<IReference> GetReferencesToLoadAndSaveReferencePriority(IReadOnlyList<IVBProject> projects)
private ICollection<IReference> GetReferencesToLoadAndSaveReferencePriority(IReadOnlyList<IVBProject> projects)
{
var referencesToLoad = new List<IReference>();

Expand Down
81 changes: 70 additions & 11 deletions Rubberduck.VBEEditor/Events/VBENativeServices.cs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
using System;
using System.Collections.Generic;
using System.Diagnostics;
using System.Linq;
using System.Text;
using Rubberduck.VBEditor.SafeComWrappers;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
Expand Down Expand Up @@ -64,6 +63,7 @@ public static void UnhookEvents()
info.Subclass.Dispose();
}
VBEEvents.Terminate();
_vbe = null;
}
}

Expand Down Expand Up @@ -113,7 +113,10 @@ private static void AttachWindow(IntPtr hwnd)
{
Debug.Assert(!TrackedWindows.ContainsKey(hwnd));
var window = GetWindowFromHwnd(hwnd);
if (window == null) return;
if (window == null)
{
return;
}
var source = window.Type == WindowKind.CodeWindow
? new CodePaneSubclass(hwnd, GetCodePaneFromHwnd(hwnd)) as IWindowEventProvider
: new DesignerWindowSubclass(hwnd);
Expand Down Expand Up @@ -162,20 +165,28 @@ private static void FocusDispatcher(object sender, WindowChangedEventArgs eventA
public static event EventHandler<SelectionChangedEventArgs> SelectionChanged;
private static void OnSelectionChanged(IntPtr hwnd)
{
var pane = GetCodePaneFromHwnd(hwnd);
if (pane != null) SelectionChanged?.Invoke(_vbe, new SelectionChangedEventArgs(pane));
using (var pane = GetCodePaneFromHwnd(hwnd))
{
if (pane != null)
{
SelectionChanged?.Invoke(_vbe, new SelectionChangedEventArgs(pane));
}
}
}

public static event EventHandler<AutoCompleteEventArgs> KeyDown;
private static void OnKeyDown(KeyPressEventArgs e)
{
using (var pane = GetCodePaneFromHwnd(e.Hwnd))
{
using (var module = pane.CodeModule)
if (pane != null)
{
var args = new AutoCompleteEventArgs(module, e);
KeyDown?.Invoke(_vbe, args);
e.Handled = args.Handled;
using (var module = pane.CodeModule)
{
var args = new AutoCompleteEventArgs(module, e);
KeyDown?.Invoke(_vbe, args);
e.Handled = args.Handled;
}
}
}
}
Expand All @@ -188,12 +199,40 @@ private static void OnWindowFocusChange(object sender, WindowChangedEventArgs ev

private static ICodePane GetCodePaneFromHwnd(IntPtr hwnd)
{
if (_vbe == null)
{
return null;
}

try
{
var caption = hwnd.GetWindowText();
using (var panes = _vbe.CodePanes)
{
return panes.FirstOrDefault(x => x.Window.Caption.Equals(caption));
var foundIt = false;
foreach (var pane in panes)
{
try
{
using (var window = pane.Window)
{
if (window.Caption.Equals(caption))
{
foundIt = true;
return pane;
}
}
}
finally
{
if(!foundIt)
{
pane.Dispose();
}
}
}

return null;
}
}
catch
Expand All @@ -207,15 +246,35 @@ private static ICodePane GetCodePaneFromHwnd(IntPtr hwnd)

private static IWindow GetWindowFromHwnd(IntPtr hwnd)
{
if (!User32.IsWindow(hwnd))
if (!User32.IsWindow(hwnd) || _vbe == null)
{
return null;
}

var caption = hwnd.GetWindowText();
using (var windows = _vbe.Windows)
{
return windows.FirstOrDefault(x => x.Caption.Equals(caption));
var foundIt = false;
foreach (var window in windows)
{
try
{
if (window.Caption.Equals(caption))
{
foundIt = true;
return window;
}

}
finally
{
if (!foundIt)
{
window.Dispose();
}
}
}
return null;
}
}

Expand Down

0 comments on commit 27f33e3

Please sign in to comment.