Skip to content

Commit 18568e5

Browse files
authored
Merge pull request #2570 from comintern/next
COM collector fixes.
2 parents 29ff445 + 6c518e3 commit 18568e5

39 files changed

+231
-114
lines changed

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
using Ninject.Modules;
88
using Rubberduck.Common;
99
using Rubberduck.Parsing;
10+
using Rubberduck.Parsing.ComReflection;
1011
using Rubberduck.Parsing.Symbols.DeclarationLoaders;
1112
using Rubberduck.Parsing.VBA;
1213
using Rubberduck.Settings;

RetailCoder.VBE/UI/Command/MenuItems/CommandBars/SerializeDeclarationsCommandMenuItem.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System;
22
using System.IO;
33
using NLog;
4+
using Rubberduck.Parsing.ComReflection;
45
using Rubberduck.Parsing.Symbols;
56
using Rubberduck.Parsing.VBA;
67
using Rubberduck.SettingsProvider;

Rubberduck.Parsing/ComReflection/ComCoClass.cs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,11 @@ public IEnumerable<ComMember> Members
4141
get { return ImplementedInterfaces.Where(x => !_events.Contains(x)).SelectMany(i => i.Members); }
4242
}
4343

44+
public ComMember DefaultMember
45+
{
46+
get { return DefaultInterface.DefaultMember; }
47+
}
48+
4449
public IEnumerable<ComMember> SourceMembers
4550
{
4651
get { return _events.SelectMany(i => i.Members); }

Rubberduck.Parsing/ComReflection/ComField.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System.Diagnostics;
22
using System.Runtime.InteropServices;
33
using System.Runtime.InteropServices.ComTypes;
4-
using System.Xml.Schema;
54
using Rubberduck.Parsing.Symbols;
65
using VARDESC = System.Runtime.InteropServices.ComTypes.VARDESC;
76
using VARFLAGS = System.Runtime.InteropServices.ComTypes.VARFLAGS;

Rubberduck.Parsing/ComReflection/ComInterface.cs

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@ public class ComInterface : ComType, IComTypeWithMembers
1616
{
1717
private readonly List<ComInterface> _inherited = new List<ComInterface>();
1818
private readonly List<ComMember> _members = new List<ComMember>();
19+
private ComMember _defaultMember;
1920

2021
public bool IsExtensible { get; private set; }
2122

@@ -29,6 +30,11 @@ public IEnumerable<ComMember> Members
2930
get { return _members; }
3031
}
3132

33+
public ComMember DefaultMember
34+
{
35+
get { return _defaultMember; }
36+
}
37+
3238
public ComInterface(ITypeInfo info, TYPEATTR attrib) : base(info, attrib)
3339
{
3440
GetImplementedInterfaces(info, attrib);
@@ -78,7 +84,12 @@ private void GetComMembers(ITypeInfo info, TYPEATTR attrib)
7884
{
7985
continue;
8086
}
81-
_members.Add(new ComMember(info, member));
87+
var comMember = new ComMember(info, member);
88+
_members.Add(comMember);
89+
if (comMember.IsDefault)
90+
{
91+
_defaultMember = comMember;
92+
}
8293
info.ReleaseFuncDesc(memberPtr);
8394
}
8495
}

Rubberduck.Parsing/ComReflection/ComMember.cs

Lines changed: 17 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,18 @@
1212

1313
namespace Rubberduck.Parsing.ComReflection
1414
{
15+
internal enum DispId
16+
{
17+
Collect = -8, //The method you are calling through Invoke is an accessor function.
18+
Destructor = -7, //The C++ destructor function for the object.
19+
Construtor = -6, //The C++ constructor function for the object.
20+
Evaluate = -5, //This method is implicitly invoked when the ActiveX client encloses the arguments in square brackets.
21+
NewEnum = -4, //It returns an enumerator object that supports IEnumVARIANT.
22+
PropertyPut = -3, //The parameter that receives the value of an assignment in a PROPERTYPUT.
23+
Unknown = -1, //The value returned by IDispatch::GetIDsOfNames to indicate that a member or parameter name was not found.
24+
Value = 0 //The default member for the object.
25+
}
26+
1527
[DebuggerDisplay("{MemberDeclaration}")]
1628
public class ComMember : ComBase
1729
{
@@ -20,6 +32,8 @@ public class ComMember : ComBase
2032
public bool ReturnsWithEventsObject { get; private set; }
2133
public bool IsDefault { get; private set; }
2234
public bool IsEnumerator { get; private set; }
35+
//This member is called on an interface when a bracketed expression is dereferenced.
36+
public bool IsEvaluateFunction { get; private set; }
2337
public ComParameter ReturnType { get; private set; }
2438
public List<ComParameter> Parameters { get; set; }
2539

@@ -30,8 +44,9 @@ public ComMember(ITypeInfo info, FUNCDESC funcDesc) : base(info, funcDesc)
3044
IsHidden = flags.HasFlag(FUNCFLAGS.FUNCFLAG_FHIDDEN);
3145
IsRestricted = flags.HasFlag(FUNCFLAGS.FUNCFLAG_FRESTRICTED);
3246
ReturnsWithEventsObject = flags.HasFlag(FUNCFLAGS.FUNCFLAG_FSOURCE);
33-
IsDefault = flags.HasFlag(FUNCFLAGS.FUNCFLAG_FUIDEFAULT);
34-
IsEnumerator = flags.HasFlag(FUNCFLAGS.FUNCFLAG_FNONBROWSABLE) && Name.Equals("_NewEnum");
47+
IsDefault = Index == (int)DispId.Value;
48+
IsEnumerator = Index == (int)DispId.NewEnum;
49+
IsEvaluateFunction = Index == (int)DispId.Evaluate;
3550
SetDeclarationType(funcDesc, info);
3651
}
3752

Rubberduck.Parsing/ComReflection/ComModule.cs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Diagnostics;
4-
using System.Linq;
54
using System.Runtime.InteropServices;
65
using System.Runtime.InteropServices.ComTypes;
76
using Rubberduck.Parsing.Symbols;
@@ -20,6 +19,11 @@ public IEnumerable<ComMember> Members
2019
get { return _members; }
2120
}
2221

22+
public ComMember DefaultMember
23+
{
24+
get { return null; }
25+
}
26+
2327
private readonly List<ComField> _fields = new List<ComField>();
2428
public IEnumerable<ComField> Fields
2529
{

Rubberduck.Parsing/ComReflection/ComProject.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -120,8 +120,6 @@ private void LoadModules(ITypeLib typeLibrary)
120120
if (type != null) KnownTypes.TryAdd(typeAttributes.guid, coclass);
121121
break;
122122
case TYPEKIND.TKIND_ALIAS:
123-
case TYPEKIND.TKIND_UNION:
124-
125123
//The current handling of this is wrong - these don't have to be classes or interfaces. In the VBE module for example,
126124
//"LongPtr" is defined as an alias to "Long" (at least on a 32 bit system) - RD is currently treating is like a class.
127125
//Unclear if these can *also* define alternative names for interfaces as well, but all the ones I've seen have been basically
@@ -141,6 +139,9 @@ private void LoadModules(ITypeLib typeLibrary)
141139
_modules.Add(module as ComModule);
142140
if (type != null) KnownTypes.TryAdd(typeAttributes.guid, module);
143141
break;
142+
case TYPEKIND.TKIND_UNION:
143+
//TKIND_UNION is not a supported member type in VBA.
144+
break;
144145
default:
145146
throw new NotImplementedException(string.Format("Didn't expect a TYPEATTR with multiple typekind flags set in {0}.", Path));
146147
}

Rubberduck.Parsing/ComReflection/ComType.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,12 +9,13 @@ public interface IComType : IComBase
99
bool IsAppObject { get; }
1010
bool IsPreDeclared { get; }
1111
bool IsHidden { get; }
12-
bool IsRestricted { get; }
12+
bool IsRestricted { get; }
1313
}
1414

1515
public interface IComTypeWithMembers : IComType
1616
{
1717
IEnumerable<ComMember> Members { get; }
18+
ComMember DefaultMember { get; }
1819
}
1920

2021
public interface IComTypeWithFields : IComType

Rubberduck.Parsing/Symbols/ReferencedDeclarationsCollector.cs renamed to Rubberduck.Parsing/ComReflection/ReferencedDeclarationsCollector.cs

Lines changed: 49 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -2,15 +2,15 @@
22
using System.Collections.Generic;
33
using System.ComponentModel;
44
using System.IO;
5+
using System.Linq;
56
using System.Runtime.InteropServices;
67
using System.Runtime.InteropServices.ComTypes;
7-
using Rubberduck.Parsing.ComReflection;
8+
using Rubberduck.Parsing.Symbols;
89
using Rubberduck.Parsing.VBA;
910
using Rubberduck.VBEditor;
10-
using System.Linq;
1111
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1212

13-
namespace Rubberduck.Parsing.Symbols
13+
namespace Rubberduck.Parsing.ComReflection
1414
{
1515
public class ReferencedDeclarationsCollector
1616
{
@@ -139,29 +139,19 @@ public List<Declaration> LoadDeclarationsFromLibrary()
139139
? string.Format("_{0}", module.Name)
140140
: module.Name);
141141

142-
var attributes = new Attributes();
143-
if (module.IsPreDeclared)
144-
{
145-
attributes.AddPredeclaredIdTypeAttribute();
146-
}
147-
if (module.IsAppObject)
148-
{
149-
attributes.AddGlobalClassAttribute();
150-
}
151-
152-
var declaration = CreateModuleDeclaration(module, moduleName, project, attributes);
142+
var declaration = CreateModuleDeclaration(module, moduleName, project, GetModuleAttributes(module));
153143
var moduleTree = new SerializableDeclarationTree(declaration);
154144
_declarations.Add(declaration);
155145
_serialized.AddDeclaration(moduleTree);
156146

157147
var membered = module as IComTypeWithMembers;
158148
if (membered != null)
159149
{
160-
CreateMemberDeclarations(membered.Members, moduleName, declaration, moduleTree);
150+
CreateMemberDeclarations(membered.Members, moduleName, declaration, moduleTree, membered.DefaultMember);
161151
var coClass = membered as ComCoClass;
162152
if (coClass != null)
163153
{
164-
CreateMemberDeclarations(coClass.SourceMembers, moduleName, declaration, moduleTree, true);
154+
CreateMemberDeclarations(coClass.SourceMembers, moduleName, declaration, moduleTree, coClass.DefaultMember, true);
165155
}
166156
}
167157

@@ -204,8 +194,26 @@ public List<Declaration> LoadDeclarationsFromLibrary()
204194
return _declarations;
205195
}
206196

197+
private static Attributes GetModuleAttributes(IComType module)
198+
{
199+
var attributes = new Attributes();
200+
if (module.IsPreDeclared)
201+
{
202+
attributes.AddPredeclaredIdTypeAttribute();
203+
}
204+
if (module.IsAppObject)
205+
{
206+
attributes.AddGlobalClassAttribute();
207+
}
208+
if (module as ComInterface != null && ((ComInterface)module).IsExtensible)
209+
{
210+
attributes.AddExtensibledClassAttribute();
211+
}
212+
return attributes;
213+
}
214+
207215
private void CreateMemberDeclarations(IEnumerable<ComMember> members, QualifiedModuleName moduleName, Declaration declaration,
208-
SerializableDeclarationTree moduleTree, bool eventHandlers = false)
216+
SerializableDeclarationTree moduleTree, ComMember defaultMember, bool eventHandlers = false)
209217
{
210218
foreach (var item in members.Where(m => !m.IsRestricted && !IgnoredInterfaceMembers.Contains(m.Name)))
211219
{
@@ -222,7 +230,7 @@ private void CreateMemberDeclarations(IEnumerable<ComMember> members, QualifiedM
222230
memberTree.AddChildren(hasParams.Parameters);
223231
}
224232
var coClass = memberDeclaration as ClassModuleDeclaration;
225-
if (coClass != null && item.IsDefault)
233+
if (coClass != null && item == defaultMember)
226234
{
227235
coClass.DefaultMember = memberDeclaration;
228236
}
@@ -262,20 +270,7 @@ private Declaration CreateModuleDeclaration(IComType module, QualifiedModuleName
262270

263271
private Declaration CreateMemberDeclaration(ComMember member, QualifiedModuleName module, Declaration parent, bool handler)
264272
{
265-
var attributes = new Attributes();
266-
if (member.IsEnumerator)
267-
{
268-
attributes.AddEnumeratorMemberAttribute(member.Name);
269-
}
270-
else if (member.IsDefault)
271-
{
272-
attributes.AddDefaultMemberAttribute(member.Name);
273-
}
274-
else if (member.IsHidden)
275-
{
276-
attributes.AddHiddenMemberAttribute(member.Name);
277-
}
278-
273+
var attributes = GetMemberAttibutes(member);
279274
switch (member.Type)
280275
{
281276
case DeclarationType.Procedure:
@@ -292,5 +287,27 @@ private Declaration CreateMemberDeclaration(ComMember member, QualifiedModuleNam
292287
throw new InvalidEnumArgumentException(string.Format("Unexpected DeclarationType {0} encountered.", member.Type));
293288
}
294289
}
290+
291+
private static Attributes GetMemberAttibutes(ComMember member)
292+
{
293+
var attributes = new Attributes();
294+
if (member.IsEnumerator)
295+
{
296+
attributes.AddEnumeratorMemberAttribute(member.Name);
297+
}
298+
else if (member.IsDefault)
299+
{
300+
attributes.AddDefaultMemberAttribute(member.Name);
301+
}
302+
else if (member.IsHidden)
303+
{
304+
attributes.AddHiddenMemberAttribute(member.Name);
305+
}
306+
else if (member.IsEvaluateFunction)
307+
{
308+
attributes.AddEvaluateMemberAttribute(member.Name);
309+
}
310+
return attributes;
311+
}
295312
}
296313
}

0 commit comments

Comments
 (0)