Skip to content

Commit 1de88d4

Browse files
authored
Merge pull request #2462 from comintern/next
Big refactor of COM reflection. All your TypeLib are belong to us.
2 parents c967df5 + 3c36eda commit 1de88d4

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

42 files changed

+1634
-773
lines changed

RetailCoder.VBE/Inspections/UnassignedVariableUsageInspection.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -30,8 +30,9 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3030
&& !declaration.IsSelfAssigned
3131
&& !declaration.References.Any(reference => reference.IsAssignment));
3232

33-
var lenFunction = BuiltInDeclarations.SingleOrDefault(s => s.Scope == "VBE7.DLL;VBA.Strings.Len");
34-
var lenbFunction = BuiltInDeclarations.SingleOrDefault(s => s.Scope == "VBE7.DLL;VBA.Strings.LenB");
33+
//The parameter scoping was apparently incorrect before - need to filter for the actual function.
34+
var lenFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.Len"));
35+
var lenbFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.Len"));
3536

3637
return from issue in declarations
3738
where issue.References.Any()

RetailCoder.VBE/Settings/WindowSettings.cs

Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,11 @@
11
using System.Xml.Serialization;
2+
using Rubberduck.Properties;
3+
using Rubberduck.UI;
4+
using Rubberduck.UI.CodeExplorer;
5+
using Rubberduck.UI.Inspections;
6+
using Rubberduck.UI.SourceControl;
7+
using Rubberduck.UI.ToDoItems;
8+
using Rubberduck.UI.UnitTesting;
29

310
namespace Rubberduck.Settings
411
{
@@ -9,6 +16,8 @@ public interface IWindowSettings
916
bool SourceControlVisibleOnStartup { get; set; }
1017
bool TestExplorerVisibleOnStartup { get; set; }
1118
bool TodoExplorerVisibleOnStartup { get; set; }
19+
20+
bool IsWindowVisible(DockableToolwindowPresenter candidate);
1221
}
1322

1423
[XmlType(AnonymousType = true)]
@@ -34,5 +43,33 @@ public WindowSettings(bool codeExplorerVisibleOnStartup, bool codeInspectionsVis
3443
public bool SourceControlVisibleOnStartup { get; set; }
3544
public bool TestExplorerVisibleOnStartup { get; set; }
3645
public bool TodoExplorerVisibleOnStartup { get; set; }
46+
47+
public bool IsWindowVisible(DockableToolwindowPresenter candidate)
48+
{
49+
//I'm sure there's a better way to do this, because this is a lazy-ass way to do it.
50+
//We're injecting into the base class, so check the derived class:
51+
if (candidate is CodeExplorerDockablePresenter)
52+
{
53+
return CodeExplorerVisibleOnStartup;
54+
}
55+
if (candidate is CodeInspectionsDockablePresenter)
56+
{
57+
return CodeInspectionsVisibleOnStartup;
58+
}
59+
if (candidate is SourceControlDockablePresenter)
60+
{
61+
return SourceControlVisibleOnStartup;
62+
}
63+
if (candidate is TestExplorerDockablePresenter)
64+
{
65+
return TestExplorerVisibleOnStartup;
66+
}
67+
if (candidate is ToDoExplorerDockablePresenter)
68+
{
69+
return TodoExplorerVisibleOnStartup;
70+
}
71+
//Oh. Hello. I have no clue who you are...
72+
return false;
73+
}
3774
}
3875
}

RetailCoder.VBE/UI/CodeExplorer/CodeExplorerDockablePresenter.cs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,13 @@
1-
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1+
using Rubberduck.Settings;
2+
using Rubberduck.SettingsProvider;
3+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
24

35
namespace Rubberduck.UI.CodeExplorer
46
{
57
public class CodeExplorerDockablePresenter : DockableToolwindowPresenter
68
{
7-
public CodeExplorerDockablePresenter(IVBE vbe, IAddIn addIn, CodeExplorerWindow view)
8-
: base(vbe, addIn, view)
9+
public CodeExplorerDockablePresenter(IVBE vbe, IAddIn addIn, CodeExplorerWindow view, IConfigProvider<WindowSettings> settings)
10+
: base(vbe, addIn, view, settings)
911
{
1012
}
1113
}

RetailCoder.VBE/UI/Controls/SearchResultsDockablePresenter.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,8 @@ namespace Rubberduck.UI.Controls
44
{
55
public class SearchResultsDockablePresenter : DockableToolwindowPresenter
66
{
7-
public SearchResultsDockablePresenter(IVBE vbe, IAddIn addin, IDockableUserControl view)
8-
: base(vbe, addin, view)
7+
public SearchResultsDockablePresenter(IVBE vbe, IAddIn addin, IDockableUserControl view)
8+
: base(vbe, addin, view, null)
99
{
1010
}
1111

RetailCoder.VBE/UI/DockableToolwindowPresenter.cs

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,10 @@
11
using System;
2+
using System.Configuration;
23
using System.Runtime.InteropServices;
34
using System.Windows.Forms;
45
using NLog;
6+
using Rubberduck.Settings;
7+
using Rubberduck.SettingsProvider;
58
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
69

710
namespace Rubberduck.UI
@@ -23,13 +26,18 @@ public abstract class DockableToolwindowPresenter : IDockablePresenter, IDisposa
2326
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
2427
private readonly IWindow _window;
2528
private readonly UserControl _userControl;
29+
private readonly WindowSettings _settings; //Storing this really doesn't matter - it's only checked on startup and never persisted.
2630

27-
protected DockableToolwindowPresenter(IVBE vbe, IAddIn addin, IDockableUserControl view)
31+
protected DockableToolwindowPresenter(IVBE vbe, IAddIn addin, IDockableUserControl view, IConfigProvider<WindowSettings> settingsProvider)
2832
{
2933
_vbe = vbe;
3034
_addin = addin;
3135
Logger.Trace(string.Format("Initializing Dockable Panel ({0})", GetType().Name));
3236
_userControl = view as UserControl;
37+
if (settingsProvider != null)
38+
{
39+
_settings = settingsProvider.Create();
40+
}
3341
_window = CreateToolWindow(view);
3442
}
3543

@@ -69,7 +77,7 @@ private IWindow CreateToolWindow(IDockableUserControl control)
6977

7078
EnsureMinimumWindowSize(toolWindow);
7179

72-
toolWindow.IsVisible = false; //hide it again
80+
toolWindow.IsVisible = _settings != null && _settings.IsWindowVisible(this);
7381

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

RetailCoder.VBE/UI/IdentifierReferences/IdentifierReferencesListDockablePresenter.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ namespace Rubberduck.UI.IdentifierReferences
77
public class IdentifierReferencesListDockablePresenter : DockableToolwindowPresenter
88
{
99
public IdentifierReferencesListDockablePresenter(IVBE vbe, IAddIn addin, SimpleListControl control, Declaration target)
10-
: base(vbe, addin, control)
10+
: base(vbe, addin, control, null)
1111
{
1212
BindTarget(target);
1313
}

RetailCoder.VBE/UI/IdentifierReferences/ImplementationsListDockablePresenter.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ namespace Rubberduck.UI.IdentifierReferences
99
public class ImplementationsListDockablePresenter : DockableToolwindowPresenter
1010
{
1111
public ImplementationsListDockablePresenter(IVBE vbe, IAddIn addin, IDockableUserControl control, IEnumerable<Declaration> implementations)
12-
: base(vbe, addin, control)
12+
: base(vbe, addin, control, null)
1313
{
1414
BindTarget(implementations);
1515
}

RetailCoder.VBE/UI/Inspections/CodeInspectionsDockablePresenter.cs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,13 @@
1-
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1+
using Rubberduck.Settings;
2+
using Rubberduck.SettingsProvider;
3+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
24

35
namespace Rubberduck.UI.Inspections
46
{
57
public class CodeInspectionsDockablePresenter : DockableToolwindowPresenter
68
{
7-
public CodeInspectionsDockablePresenter(IVBE vbe, IAddIn addin, CodeInspectionsWindow window)
8-
:base(vbe, addin, window)
9+
public CodeInspectionsDockablePresenter(IVBE vbe, IAddIn addin, CodeInspectionsWindow window, IConfigProvider<WindowSettings> settings)
10+
: base(vbe, addin, window, settings)
911
{
1012
}
1113
}

RetailCoder.VBE/UI/ParserErrors/ParserErrorsPresenter.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ public interface IParserErrorsPresenter
1717
public class ParserErrorsPresenter : DockableToolwindowPresenter, IParserErrorsPresenter
1818
{
1919
public ParserErrorsPresenter(IVBE vbe, IAddIn addin)
20-
: base(vbe, addin, new SimpleListControl(RubberduckUI.ParseErrors_Caption))
20+
: base(vbe, addin, new SimpleListControl(RubberduckUI.ParseErrors_Caption), null)
2121
{
2222
_source = new BindingList<ParseErrorListItem>();
2323
var control = UserControl as SimpleListControl;

RetailCoder.VBE/UI/SourceControl/SourceControlDockablePresenter.cs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
11
using System.Diagnostics;
2+
using Rubberduck.Settings;
3+
using Rubberduck.SettingsProvider;
24
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
35

46
namespace Rubberduck.UI.SourceControl
@@ -8,8 +10,8 @@ namespace Rubberduck.UI.SourceControl
810
/// </summary>
911
public class SourceControlDockablePresenter : DockableToolwindowPresenter
1012
{
11-
public SourceControlDockablePresenter(IVBE vbe, IAddIn addin, SourceControlPanel window)
12-
: base(vbe, addin, window)
13+
public SourceControlDockablePresenter(IVBE vbe, IAddIn addin, SourceControlPanel window, IConfigProvider<WindowSettings> settings)
14+
: base(vbe, addin, window, settings)
1315
{
1416
}
1517

RetailCoder.VBE/UI/ToDoItems/ToDoExplorerDockablePresenter.cs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
1-
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1+
using Rubberduck.Settings;
2+
using Rubberduck.SettingsProvider;
3+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
24

35
namespace Rubberduck.UI.ToDoItems
46
{
@@ -7,8 +9,8 @@ namespace Rubberduck.UI.ToDoItems
79
/// </summary>
810
public class ToDoExplorerDockablePresenter : DockableToolwindowPresenter
911
{
10-
public ToDoExplorerDockablePresenter(IVBE vbe, IAddIn addin, ToDoExplorerWindow window)
11-
: base(vbe, addin, window)
12+
public ToDoExplorerDockablePresenter(IVBE vbe, IAddIn addin, ToDoExplorerWindow window, IConfigProvider<WindowSettings> settings)
13+
: base(vbe, addin, window, settings)
1214
{
1315
}
1416
}

RetailCoder.VBE/UI/UnitTesting/TestExplorerDockablePresenter.cs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,13 @@
1-
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1+
using Rubberduck.Settings;
2+
using Rubberduck.SettingsProvider;
3+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
24

35
namespace Rubberduck.UI.UnitTesting
46
{
57
public class TestExplorerDockablePresenter : DockableToolwindowPresenter
68
{
7-
public TestExplorerDockablePresenter(IVBE vbe, IAddIn addin, TestExplorerWindow view)
8-
: base(vbe, addin, view)
9+
public TestExplorerDockablePresenter(IVBE vbe, IAddIn addin, TestExplorerWindow view, IConfigProvider<WindowSettings> settings)
10+
: base(vbe, addin, view, settings)
911
{
1012
}
1113
}
Lines changed: 52 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,52 @@
1+
using System;
2+
using System.Diagnostics;
3+
using System.Runtime.InteropServices.ComTypes;
4+
using Rubberduck.Parsing.Symbols;
5+
using FUNCDESC = System.Runtime.InteropServices.ComTypes.FUNCDESC;
6+
7+
namespace Rubberduck.Parsing.ComReflection
8+
{
9+
public interface IComBase
10+
{
11+
Guid Guid { get; }
12+
int Index { get; }
13+
ComDocumentation Documentation { get; }
14+
string Name { get; }
15+
DeclarationType Type { get; }
16+
}
17+
18+
public abstract class ComBase : IComBase
19+
{
20+
public Guid Guid { get; protected set; }
21+
public int Index { get; protected set; }
22+
public ComDocumentation Documentation { get; protected set; }
23+
public string Name
24+
{
25+
get { return Documentation == null ? string.Empty : Documentation.Name; }
26+
}
27+
28+
public DeclarationType Type { get; protected set; }
29+
30+
protected ComBase(ITypeLib typeLib, int index)
31+
{
32+
Index = index;
33+
Documentation = new ComDocumentation(typeLib, index);
34+
}
35+
36+
protected ComBase(ITypeInfo info)
37+
{
38+
ITypeLib typeLib;
39+
int index;
40+
info.GetContainingTypeLib(out typeLib, out index);
41+
Index = index;
42+
Debug.Assert(typeLib != null);
43+
Documentation = new ComDocumentation(typeLib, index);
44+
}
45+
46+
protected ComBase(ITypeInfo info, FUNCDESC funcDesc)
47+
{
48+
Index = funcDesc.memid;
49+
Documentation = new ComDocumentation(info, funcDesc.memid);
50+
}
51+
}
52+
}
Lines changed: 87 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,87 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Diagnostics;
4+
using System.Linq;
5+
using System.Runtime.InteropServices;
6+
using System.Runtime.InteropServices.ComTypes;
7+
using Rubberduck.Parsing.Symbols;
8+
using TYPEATTR = System.Runtime.InteropServices.ComTypes.TYPEATTR;
9+
using IMPLTYPEFLAGS = System.Runtime.InteropServices.ComTypes.IMPLTYPEFLAGS;
10+
11+
namespace Rubberduck.Parsing.ComReflection
12+
{
13+
public class ComCoClass : ComType, IComTypeWithMembers
14+
{
15+
private readonly Dictionary<ComInterface, bool> _interfaces = new Dictionary<ComInterface, bool>();
16+
private readonly List<ComInterface> _events = new List<ComInterface>();
17+
18+
public ComInterface DefaultInterface { get; private set; }
19+
20+
public IEnumerable<ComInterface> EventInterfaces
21+
{
22+
get { return _events; }
23+
}
24+
public IEnumerable<ComInterface> ImplementedInterfaces
25+
{
26+
get { return _interfaces.Keys; }
27+
}
28+
29+
public IEnumerable<ComInterface> VisibleInterfaces
30+
{
31+
get { return _interfaces.Where(i => !i.Value).Select(i => i.Key); }
32+
}
33+
34+
public IEnumerable<ComMember> Members
35+
{
36+
get { return ImplementedInterfaces.SelectMany(i => i.Members); }
37+
}
38+
39+
public bool WithEvents
40+
{
41+
get { return _events.Count > 0; }
42+
}
43+
44+
public ComCoClass(ITypeLib typeLib, ITypeInfo info, TYPEATTR attrib, int index) : base (typeLib, attrib, index)
45+
{
46+
Type = DeclarationType.ClassModule;
47+
GetImplementedInterfaces(info, attrib);
48+
Debug.Assert(attrib.cFuncs == 0);
49+
}
50+
51+
private void GetImplementedInterfaces(ITypeInfo info, TYPEATTR typeAttr)
52+
{
53+
for (var implIndex = 0; implIndex < typeAttr.cImplTypes; implIndex++)
54+
{
55+
int href;
56+
info.GetRefTypeOfImplType(implIndex, out href);
57+
58+
ITypeInfo implemented;
59+
info.GetRefTypeInfo(href, out implemented);
60+
61+
IntPtr attribPtr;
62+
implemented.GetTypeAttr(out attribPtr);
63+
var attribs = (TYPEATTR)Marshal.PtrToStructure(attribPtr, typeof(TYPEATTR));
64+
65+
ComType inherited;
66+
ComProject.KnownTypes.TryGetValue(attribs.guid, out inherited);
67+
var intface = inherited as ComInterface ?? new ComInterface(implemented, attribs);
68+
ComProject.KnownTypes.TryAdd(attribs.guid, intface);
69+
70+
IMPLTYPEFLAGS flags = 0;
71+
try
72+
{
73+
info.GetImplTypeFlags(implIndex, out flags);
74+
}
75+
catch (COMException) { }
76+
77+
DefaultInterface = flags.HasFlag(IMPLTYPEFLAGS.IMPLTYPEFLAG_FDEFAULT) ? intface : DefaultInterface;
78+
if (flags.HasFlag(IMPLTYPEFLAGS.IMPLTYPEFLAG_FSOURCE))
79+
{
80+
_events.Add(intface);
81+
}
82+
_interfaces.Add(intface, flags.HasFlag(IMPLTYPEFLAGS.IMPLTYPEFLAG_FRESTRICTED));
83+
info.ReleaseTypeAttr(attribPtr);
84+
}
85+
}
86+
}
87+
}

0 commit comments

Comments
 (0)