Skip to content

Commit 13e5fba

Browse files
authored
Merge pull request #1882 from Hosch250/Issue1853
Make Worksheets and Workbooks know what type they are.
2 parents 05983e7 + 4068146 commit 13e5fba

File tree

5 files changed

+107
-8
lines changed

5 files changed

+107
-8
lines changed

Rubberduck.Parsing/Symbols/ClassModuleDeclaration.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,8 @@ public ClassModuleDeclaration(
1818
string name,
1919
bool isBuiltIn,
2020
IEnumerable<IAnnotation> annotations,
21-
Attributes attributes, bool hasDefaultInstanceVariable = false)
21+
Attributes attributes,
22+
bool hasDefaultInstanceVariable = false)
2223
: base(
2324
qualifiedName,
2425
projectDeclaration,

Rubberduck.Parsing/Symbols/DeclarationSymbolsListener.cs

Lines changed: 44 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -8,12 +8,14 @@
88
using System;
99
using System.Collections.Generic;
1010
using System.Linq;
11+
using System.Runtime.InteropServices;
1112
using Antlr4.Runtime.Misc;
1213

1314
namespace Rubberduck.Parsing.Symbols
1415
{
1516
public class DeclarationSymbolsListener : VBAParserBaseListener
1617
{
18+
private readonly RubberduckParserState _state;
1719
private readonly QualifiedModuleName _qualifiedName;
1820
private readonly Declaration _moduleDeclaration;
1921
private readonly Declaration _projectDeclaration;
@@ -22,33 +24,29 @@ public class DeclarationSymbolsListener : VBAParserBaseListener
2224
private Declaration _currentScopeDeclaration;
2325
private Declaration _parentDeclaration;
2426

25-
private readonly IEnumerable<CommentNode> _comments;
2627
private readonly IEnumerable<IAnnotation> _annotations;
2728
private readonly IDictionary<Tuple<string, DeclarationType>, Attributes> _attributes;
28-
private readonly HashSet<ReferencePriorityMap> _projectReferences;
2929

3030
private readonly List<Declaration> _createdDeclarations = new List<Declaration>();
3131
public IReadOnlyList<Declaration> CreatedDeclarations { get { return _createdDeclarations; } }
3232

3333
public DeclarationSymbolsListener(
34+
RubberduckParserState state,
3435
QualifiedModuleName qualifiedName,
3536
vbext_ComponentType type,
36-
IEnumerable<CommentNode> comments,
3737
IEnumerable<IAnnotation> annotations,
3838
IDictionary<Tuple<string, DeclarationType>, Attributes> attributes,
39-
HashSet<ReferencePriorityMap> projectReferences,
4039
Declaration projectDeclaration)
4140
{
41+
_state = state;
4242
_qualifiedName = qualifiedName;
43-
_comments = comments;
4443
_annotations = annotations;
4544
_attributes = attributes;
4645

4746
var declarationType = type == vbext_ComponentType.vbext_ct_StdModule
4847
? DeclarationType.ProceduralModule
4948
: DeclarationType.ClassModule;
5049

51-
_projectReferences = projectReferences;
5250
_projectDeclaration = projectDeclaration;
5351

5452
var key = Tuple.Create(_qualifiedName.ComponentName, declarationType);
@@ -69,6 +67,41 @@ public DeclarationSymbolsListener(
6967
else
7068
{
7169
bool hasDefaultInstanceVariable = type != vbext_ComponentType.vbext_ct_ClassModule && type != vbext_ComponentType.vbext_ct_StdModule;
70+
71+
Declaration superType = null;
72+
if (type == vbext_ComponentType.vbext_ct_Document)
73+
{
74+
foreach (var coclass in _state.CoClasses)
75+
{
76+
try
77+
{
78+
if (coclass.Key.Count != _qualifiedName.Component.Properties.Count)
79+
{
80+
continue;
81+
}
82+
83+
var allNamesMatch = true;
84+
for (var i = 0; i < coclass.Key.Count; i++)
85+
{
86+
if (coclass.Key[i] != _qualifiedName.Component.Properties.Item(i + 1).Name)
87+
{
88+
allNamesMatch = false;
89+
break;
90+
}
91+
}
92+
93+
if (allNamesMatch)
94+
{
95+
superType = coclass.Value;
96+
break;
97+
}
98+
}
99+
catch (COMException)
100+
{
101+
}
102+
}
103+
}
104+
72105
_moduleDeclaration = new ClassModuleDeclaration(
73106
_qualifiedName.QualifyMemberName(_qualifiedName.Component.Name),
74107
_projectDeclaration,
@@ -77,6 +110,11 @@ public DeclarationSymbolsListener(
77110
FindAnnotations(),
78111
moduleAttributes,
79112
hasDefaultInstanceVariable: hasDefaultInstanceVariable);
113+
114+
if (superType != null)
115+
{
116+
((ClassModuleDeclaration) _moduleDeclaration).AddSupertype(superType);
117+
}
80118
}
81119
SetCurrentScope();
82120
AddDeclaration(_moduleDeclaration);

Rubberduck.Parsing/Symbols/ReferencedDeclarationsCollector.cs

Lines changed: 53 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -284,6 +284,11 @@ public List<Declaration> GetDeclarationsForReference(Reference reference)
284284

285285
foreach (var member in _comInformation.Values)
286286
{
287+
if (member.TypeAttributes.typekind == TYPEKIND.TKIND_COCLASS)
288+
{
289+
GetCoClassInformation(member);
290+
}
291+
287292
for (var memberIndex = 0; memberIndex < member.TypeAttributes.cFuncs; memberIndex++)
288293
{
289294
string[] memberNames;
@@ -299,6 +304,7 @@ public List<Declaration> GetDeclarationsForReference(Reference reference)
299304
member.TypeInfo.ReleaseFuncDesc(memberDescriptorPointer);
300305
continue;
301306
}
307+
302308
if (member.ModuleDeclaration.DeclarationType == DeclarationType.ClassModule &&
303309
memberDeclaration is ICanBeDefaultMember &&
304310
((ICanBeDefaultMember)memberDeclaration).IsDefaultMember)
@@ -338,6 +344,53 @@ memberDeclaration is ICanBeDefaultMember &&
338344
return output;
339345
}
340346

347+
private void GetCoClassInformation(ComInformation member)
348+
{
349+
var componentMemberNames = new List<string>();
350+
for (var implIndex = 0; implIndex < member.TypeAttributes.cImplTypes; implIndex++)
351+
{
352+
int href;
353+
member.TypeInfo.GetRefTypeOfImplType(0, out href);
354+
355+
ITypeInfo implTypeInfo;
356+
member.TypeInfo.GetRefTypeInfo(href, out implTypeInfo);
357+
358+
IntPtr typeAttributesPointer;
359+
implTypeInfo.GetTypeAttr(out typeAttributesPointer);
360+
361+
var typeAttributes = (TYPEATTR)Marshal.PtrToStructure(typeAttributesPointer, typeof(TYPEATTR));
362+
363+
for (var i = 0; i < typeAttributes.cFuncs; i++)
364+
{
365+
var memberNames = new string[255];
366+
367+
IntPtr memberDescriptorPointer;
368+
implTypeInfo.GetFuncDesc(i, out memberDescriptorPointer);
369+
var memberDescriptor = (FUNCDESC)Marshal.PtrToStructure(memberDescriptorPointer, typeof(FUNCDESC));
370+
371+
if (!(memberDescriptor.invkind.HasFlag(INVOKEKIND.INVOKE_PROPERTYGET) ||
372+
memberDescriptor.invkind.HasFlag(INVOKEKIND.INVOKE_PROPERTYPUT) ||
373+
memberDescriptor.invkind.HasFlag(INVOKEKIND.INVOKE_PROPERTYPUTREF)))
374+
{
375+
continue;
376+
}
377+
378+
int namesArrayLength;
379+
implTypeInfo.GetNames(memberDescriptor.memid, memberNames, 255, out namesArrayLength);
380+
381+
if (!IgnoredInterfaceMembers.Contains(memberNames[0]) &&
382+
!componentMemberNames.Contains(memberNames[0]))
383+
{
384+
componentMemberNames.Add(memberNames[0]);
385+
}
386+
}
387+
388+
member.TypeInfo.ReleaseTypeAttr(typeAttributesPointer);
389+
}
390+
391+
_state.CoClasses.TryAdd(componentMemberNames, member.ModuleDeclaration);
392+
}
393+
341394
private Declaration CreateMemberDeclaration(FUNCDESC memberDescriptor, TYPEKIND typeKind, ITypeInfo info, IMPLTYPEFLAGS parentImplFlags,
342395
QualifiedModuleName typeQualifiedModuleName, Declaration moduleDeclaration, out string[] memberNames)
343396
{

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -566,7 +566,7 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
566566
}
567567
}
568568
Logger.Debug("Creating declarations for module {0}.", qualifiedModuleName.Name);
569-
var declarationsListener = new DeclarationSymbolsListener(qualifiedModuleName, component.Type, _state.GetModuleComments(component), _state.GetModuleAnnotations(component), _state.GetModuleAttributes(component), _projectReferences, projectDeclaration);
569+
var declarationsListener = new DeclarationSymbolsListener(_state, qualifiedModuleName, component.Type, _state.GetModuleAnnotations(component), _state.GetModuleAttributes(component), projectDeclaration);
570570
ParseTreeWalker.Default.Walk(declarationsListener, tree);
571571
foreach (var createdDeclaration in declarationsListener.CreatedDeclarations)
572572
{

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -67,6 +67,8 @@ public sealed class RubberduckParserState : IDisposable
6767

6868
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
6969

70+
public readonly ConcurrentDictionary<List<string>, Declaration> CoClasses = new ConcurrentDictionary<List<string>, Declaration>();
71+
7072
static RubberduckParserState()
7173
{
7274
var values = Enum.GetValues(typeof(ParserState));
@@ -1032,6 +1034,11 @@ public void Dispose()
10321034
item.Value.Dispose();
10331035
}
10341036

1037+
if (CoClasses != null)
1038+
{
1039+
CoClasses.Clear();
1040+
}
1041+
10351042
_moduleStates.Clear();
10361043
_declarationSelections.Clear();
10371044
_projects.Clear();

0 commit comments

Comments
 (0)